<< >> Title Contents Index Home Help

3 Fortran Statements


This chapter describes each of the Fortran statements. Each description includes a brief summary of the statement, a syntax description, a complete description and an example. The statements are listed in alphabetical order. The first section lists terms that are used throughout the chapter.

Definition of Terms

character scalar memory reference
is an character variable, a character array element, or a character member of a structure.
integer scalar memory reference
is an integer variable, an integer array element, or an integer member of a structure.
logical scalar memory reference
is an logical variable, a logical array element, or a logical member of a structure.

ACCEPT @



The ACCEPT statement has the same syntax as the PRINT statement and causes formatted input to be read on standard input, stdin. ACCEPT is identical to the READ statement with a unit specifier of asterisk (*).

Syntax

ACCEPT f [,iolist]
ACCEPT namelist

f
format-specifier. A * indicates list directed input.
iolist
is a list of variables to be input.
namelist
is the name of a namelist specified with the NAMELIST statement.

Examples

	ACCEPT *, IA, ZA
	ACCEPT 99, I, J, K
	ACCEPT SUM
99	FORMAT(I2, I4, I3)

ALLOCATE @



The ALLOCATE statement allocates storage for each pointer-based variable and allocatable common block which appears in the statement. Allocate also declares storage for deferred-shape arrays.

Syntax

ALLOCATE ( name[, name ] ... [ , STAT= var ] )

name
is a pointer-based variable or the name of an allocatable COMMON enclosed in slashes.
var
is an integer variable, integer array element or an integer member of a STRUCTURE (that is, an integer scalar memory reference).

Description

For a pointer based variable, its associated pointer variable is defined with the address of the allocated memory area. If the specifier STAT= is present, successful execution of the ALLOCATE statement causes the status variable to be defined with a value of zero. If an error occurs during execution of the statement and the specifier STAT= is present, the status variable is defined to have the integer value one. If an error occurs and the specifier STAT= is not present, program execution is terminated.

A dynamic, or allocatable COMMON block is a common block whose storage is not allocated until an explicit ALLOCATE statement is executed.

For a deferred-shape array, the ALLOCATE statement must include the bounds of the array. Refer to the examples for details.

Examples

	COMMON P, N, M
POINTER (P, A(N,M))
COMMON, ALLOCATABLE /ALL/X(10), Y
ALLOCATE (/ALL/, A, STAT=IS)
PRINT *, IS
X(5) = A(2, 1)
DEALLOCATE (A)
DEALLOCATE (A, STAT=IS)
PRINT *, 'should be 1', IS
DEALLOCATE (/ALL/)
For a deferred shape array, the allocate must include the bounds of the array.

	REAL A(:,:)
	...
	ALLOCATE (A(1:11, M:N))

ASSIGN



The ASSIGN statement assigns a statement label to a variable.

Syntax

ASSIGN a TO b
a is the statement label.

b is an integer variable.

Description

Executing an ASSIGN statement assigns a statement label to an integer variable. This is the only way that a variable may be defined with a statement label value. The statement label must be:

A variable must be defined with a statement label when it is referenced: An integer variable defined with a statement label can be redefined with a different statement label, the same statement label or with an integer value.

Example

	  	ASSIGN 40 TO K


GO TO K


40 L = P + I + 56

BACKSPACE



When a BACKSPACE statement is executed the file connected to the specified unit is positioned before the preceding record.

Syntax

BACKSPACE unit
BACKSPACE ([UNIT=]unit [,ERR=errs] [, IOSTAT=ios])
unit
is the unit specifier.
errs
an error specifier which is a statement label of an executable statement in the same program. If an error condition occurs execution continues with the statement specified by errs.
ios
is an integer scalar memory reference which is the input/output status specifier: if this is included in list, ios becomes defined with zero if no error condition exists or a positive integer when there is an error condition.

Description

If there is no preceding record the position of the file is not changed. A BACKSPACE statement cannot be executed on a file that does not exist. You must not issue a BACKSPACE statement for a file that is open for direct or append access.

Examples

	BACKSPACE 4
	BACKSPACE ( UNIT=3 )
	BACKSPACE ( 7, IOSTAT=IOCHEK, ERR=50 )

BLOCK DATA



The BLOCK DATA statement introduces a module that sets up initial values in COMMON blocks. No executable statements are allowed in a BLOCK DATA module.

Syntax

BLOCK DATA [name]

name
is a symbol identifying the module and must be unique among all global names (COMMON block names and among all other module names). If missing, the module is given a default name.

Example

	BLOCK DATA
COMMON /SIDE/ BASE, ANGLE, HEIGHT, WIDTH
INTEGER SIZE
PARAMETER (SIZE=100)
INTEGER BASE(0:SIZE)
REAL WIDTH(0:SIZE), ANGLE(0:SIZE)
DATA/(BASE(I),I=0,SIZE)/SIZE*-1,-1/,
+ (WIDTH(I),I=0,SIZE)/SIZE*0.0,0.0/
END

BYTE @



The BYTE statement establishes the data type of a variable by explicitly attaching the name of a variable to a 1-byte integer. This overrides the implication of data typing by the initial letter of a symbolic name.

Syntax

BYTE name [/clist/], ...
name
is the symbolic name of a variable, array, or an array declarator (see the DIMENSION statement for an explanation of array declarators).
clist
is a list of constants that initialize the data, as in a DATA statement.

Description

Byte statements may be used to dimension arrays explicitly in the same way as the DIMENSION statement. BYTE declaration statements must not be labeled.

Example

	BYTE TB3, SEC, STORE (5,5)

CALL



The CALL statement transfers control to a subroutine.

Syntax

CALL subroutine [([ argument [, argument]...])]
subroutine
is the name of the subroutine.
argument
is the actual argument being passed to the subroutine. The first argument corresponds to the first dummy argument in the SUBROUTINE statement and so on.

Description

Actual arguments can be expressions including: constants, scalar variables, function references and arrays.

@ Actual arguments can also be alternate return specifiers. Alternate return specifiers are labels prefixed by asterisks (*) or ampersands (&) (the ampersand is an extension from Fortran 77).

Recursive calls are allowed using the -Mrecursive command-line option.@

Examples

	CALL CRASH       ! no arguments
CALL BANG(1.0) ! one argument
CALL WALLOP(V, INT) ! two arguments
CALL ALTRET(I, *10, *20)
SUBROUTINE ONE
DIMENSION ARR ( 10, 10 )
REAL WORK
INTEGER ROW, COL
PI=3.142857
CALL EXPENS(ARR,ROW,COL,WORK,SIN(PI/2)+3.4)
RETURN
END

CHARACTER



The CHARACTER statement establishes the data type of a variable by explicitly attaching the name of a variable to a character data type. This overrides the implication of data typing by the initial letter of a symbolic name.

Syntax

CHARACTER [*len][,] name [dimension] [*len] [/clist/], ...
name
is the symbolic name of a variable, array, or an array declarator (see the DIMENSION statement for an explanation of array declarators).
len
is a constant or *. (*) is only valid if the corresponding name is a dummy argument.
clist
is a list of constants that initialize the data, as in a DATA statement.

Description

Character type declaration statements may be used to dimension arrays explicitly in the same way as the DIMENSION statement. Type declaration statements must not be labeled. Note: The data type of a symbol may be explicitly declared only once. It is established by type declaration statement, IMPLICIT statement or by predefined typing rules. Explicit declaration of a type overrides any implicit declaration. An IMPLICIT statement overrides predefined typing rules.

Examples

	CHARACTER A*4, B*6, C
A is 4 and B is 6 characters long and C is 1 character long.


CLOSE



The CLOSE statement terminates the connection of the specified file to a unit.

Syntax

CLOSE ([UNIT=] u [,IOSTAT=ios] [,ERR= errs ] 
[,STATUS= sta] [,DISPOSE= sta] [,DISP= sta])
u
the external unit specifier where u is an integer.
ios
is an integer scalar memory reference; if this is included ios becomes defined with 0 (zero) if no error condition exists or a positive integer when there is an error condition.
errs
is an error specifier in the form of a statement label of an executable statement in the same module. If an error condition occurs, execution continues with the statement specified by errs.
sta
is a character expression, where case is insignificant, specifying the file status and the same keywords are used for the dispose status. Status can be KEEP or DELETE. KEEP cannot be specified for a file whose dispose status is SCRATCH. When KEEP is specified (for a file that exists) the file continues to exist after the CLOSE statement; conversely DELETE deletes the file after the CLOSE statement. The default value is KEEP unless the file status is SCRATCH.

Description

A unit may be the subject of a CLOSE statement from within any module. If the unit specified does not exist or has no file connected to it the use of the CLOSE statement has no effect. Provided the file is still in existence it may be reconnected to the same or a different unit after the execution of a CLOSE statement. Note that an implicit CLOSE is executed when a program stops.

Example

In the following example the file on UNIT 6 is closed and deleted.

	CLOSE(UNIT=6,STATUS='DELETE')

COMMON (Static and Dynamic)



The COMMON statement defines contiguous blocks of storage. Each block is identified by a symbolic name and the order of variables and arrays is defined in the COMMON block containing them. There are two forms of the COMMON statement, a static form and a dynamic form.

Syntax

	COMMON /name/nlist [, /name/nlist]...
@	COMMON [,ALLOCATABLE] /name/nlist [,/name/nlist]...
name
is the name of each common block and is declared between the /.../ delimiters.
nlist
is a list of scalar and array names where the arrays may be defined in DIMENSION statements or formally declared by their inclusion in the COMMON block.

Description (static COMMON)

The name of the COMMON block need not be supplied; this is the Fortran BLANK COMMON feature. In this case the compiler will use a default name which is implementation specific. There can be several COMMON block statements of the same name in a module; these are effectively treated as one statement, with variables and array addresses concatenated from one COMMON statement of the same name to the next. This is an alternative to the use of continuation lines when declaring a common block with many symbols.

Common blocks with the same name that are declared in different modules share the same storage area when combined into one executable program.

Example (static COMMON)

	DIMENSION R(10)
COMMON /HOST/ A, R, Q(3), U
This declares a common block of data memory called HOST where A will be held in the first memory location, R(1)... R(10) will be held in the next ten locations, Q(1)... Q(3) in the next three and U in the fifteenth location. Note the different types of declaration used for R (declared in a DIMENSION statement) and Q (declared in the COMMON statement). The declaration of HOST in a SUBROUTINE in the same executable program will share the same data area.
	SUBROUTINE DEMO
COMMON/HOST/STORE(15)
.
.
.
RETURN
END
If the main program has the common block declaration as in the previous example, the COMMON statement in the subroutine causes STORE(1) to correspond to A, STORE(2) to correspond to R(1), STORE(3) to correspond to R(2), and so on through to STORE(15) corresponding to the variable U.

You can name records within a COMMON block. Because the storage requirements of records are machine-dependent, the size of a COMMON block containing records may vary between machines. Note that this may also affect subsequent equivalence associations to variables within COMMON blocks that contain records.

@ Both character and non-character data may reside in one COMMON block. Data is aligned within the COMMON block in order to conform to machine-dependent alignment requirements.

A COMMON block may be data initialized in more than one program unit if the existing system environment allows it (note that COFF-based systems do not). It is up to the programmer to make sure that data within one COMMON block is not initialized more than once.

Blank COMMON may be data initialized.

Description (dynamic COMMON) @

A dynamic, or allocatable, COMMON block is a common block whose storage is not allocated until an explicit ALLOCATE statement is executed.

If the ALLOCATABLE attribute is present, all named COMMON blocks appearing in the COMMON statement are marked as allocatable. Like a normal COMMON statement, the name of an allocatable COMMON block may appear in more than one COMMON statement. Note that the ALLOCATABLE attribute need not appear in every COMMON statement.

The following restrictions apply to the dynamic COMMON statement:

Example (dynamic COMMON)


	COMMON, ALLOCATABLE /ALL1/ A, B, /ALL2/ AA, BB
COMMON /STAT/ D, /ALL1/ C
This declares the following variables:
ALL1
is an allocatable COMMON block whose members are A, B, and C.
ALL2
is an allocatable COMMON block whose members are AA, and BB.
STAT
is a statically-allocated COMMON block whose only member is D.
A reference to a member of an allocatable COMMON block appears in a Fortran statement just like a member of a normal (static) COMMON block. No special syntax is required to access members of allocatable common blocks. For example, using the above declarations, the following is a valid pgf77 statement:
AA = B * D

COMPLEX



The COMPLEX statement establishes the data type of a variable by explicitly attaching the name of a variable to a complex data type. This overrides the implication of data typing by the initial letter of a symbolic name.

Syntax

COMPLEX name [*n] [dimensions] [/clist/] [, name] [/clist/] ...
name
is the symbolic name of a variable, array, or an array declarator (see the DIMENSION statement below for an explanation of array declarators).
clist
is a list of constants that initialize the data, as in a DATA statement.

Description

COMPLEX statements may be used to dimension arrays explicitly in the same way as the DIMENSION statement. COMPLEX statements must not be labeled. Note: The data type of a symbol may be explicitly declared only once. It is established by type declaration statement, IMPLICIT statement or by predefined typing rules. Explicit declaration of a type overrides any implicit declaration. An IMPLICIT statement overrides predefined typing rules.

The default size of a COMPLEX variable is 8 bytes. With the -Mr8 option, the default size of a COMPLEX variable is 16 bytes.

Example

	COMPLEX CURRENT

CONTINUE



This CONTINUE statement passes control to the next statement. It is supplied mainly to overcome the problem that transfer of control statements are not allowed to terminate a DO loop.

Syntax

CONTINUE

Example

	   DO 100 I = 1,10
SUM = SUM + ARRAY (I)
IF(SUM .GE. 1000.0) GOTO 200
100 CONTINUE
200 ...

DATA



The DATA statement assigns initial values to variables before execution.

Syntax

DATA vlist/dlist/[[, ]vlist/dlist/]...
vlist
is a list of variable names, array element names or array names separated by commas.
dlist
is a list of constants or PARAMETER constants, separated by commas, corresponding to elements in the vlist. An array name in the vlist demands that dlist constants be supplied to fill every element of the array.
Repetition of a constant is provided by using the form:
n*constant-value
n
a positive integer, is the repetition count.

Example

	REAL A, B, C(3), D(2)
	DATA A, B, C(1), D /1.0, 2.0, 3.0, 2*4.0/
This performs the following initialization:
	A  = 1.0
	B  = 2.0
	C(1)  = 3.0
	D(1)  = 4.0
	D(2)  = 4.0

DEALLOCATE @



The DEALLOCATE statement causes the memory allocated for each pointer-based variable or allocatable COMMON block that appears in the statement to be deallocated (freed). Deallocate also deallocates storage for deferred-shape arrays.

Syntax

DEALLOCATE ( al [, a1 ] ... [ , STAT= var ] )
Where:
al
is a pointer-based variable or the name of an allocatable COMMON block enclosed in slashes.
var
is an integer variable, integer array element, or an integer member of a structure.

Description

An attempt to deallocate a pointer-based variable or an allocatable COMMON block which was not created by an ALLOCATE statement results in an error condition.

If the specifier STAT= is present, successful execution of the statement causes var to be defined with the value of zero. If an error occurs during the execution of the statement and the specifier STAT= is present, the status variable is defined to have the integer value one. If an error occurs and the specifier STAT= is not present, program execution is terminated.

Examples

	COMMON P, N, M
POINTER (P, A(N,M))
COMMON, ALLOCATABLE /ALL/X(10), Y
ALLOCATE (/ALL/, A, STAT=IS)
PRINT *, IS
X(5) = A(2, 1)
DEALLOCATE (A)
DEALLOCATE (A, STAT=IS)
PRINT *, 'should be 1', IS
DEALLOCATE (/ALL/)

DECODE @



The DECODE statement transfers data between variables or arrays in internal storage and translates that data from character form to internal form, according to format specifiers. Similar results can be accomplished using internal files with formatted sequential READ statements.

Syntax

DECODE (c, f, b [ ,IOSTAT= ios ] [, ERR= errs]) [ list ] 
c
is an integer expression specifying the number of bytes involved in translation.
f
is the format identifier.
b
is a scalar or array reference for the buffer area containing formatted data (characters).
ios
is the an integer scalar memory reference which is the input/output status specifier: if this is specified ios becomes defined with zero if no error condition exists or a positive integer when there is an error condition.
errs
an error specifier which takes the form of a statement label of an executable statement in the same program unit. If an error condition occurs execution continues with the statement specified by errs
list
is a list of input items.

DIMENSION



The DIMENSION statement defines the number of dimensions in an array and the number of elements in each dimension.

Syntax

DIMENSION name ([lb:]ub[,[lb:]ub]...) [,name([lb:]ub[,[lb:]ub]...)]
name
is the symbolic name of an array.
lb:ub
is a dimension declarator specifying the bounds for a dimension (the lower bound lb and the upper bound ub). lb and ub must be integers with ub greater than lb. The lower bound lb is optional; if it is not specified, it is taken to be 1.

Description

DIMENSION can be used in a subroutine to establish an argument as an array, and in this case the declarator can use expressions formed from integer variables and constants to establish the dimensions (adjustable arrays). Note however that these integer variables must be either arguments or declared in COMMON; they cannot be local. Note that in this case the function of DIMENSION is merely to supply a mapping of the argument to the subroutine code, and not to allocate storage.

If an array is a dummy argument its last dimension may be a * (assumed size array)

The typing of the array in a DIMENSION statement is defined by the initial letter of the array name in the same way as variable names. The letters I,J,K,L,M and N imply that the array is of INTEGER type and an array with a name starting with any of the letters A to H and O to Z will be of type REAL, unless overridden by an IMPLICIT or type declaration statement. Arrays may appear in type declaration and COMMON statements but the array name can appear in only one array declaration.

DIMENSION statements must not be labeled.

Example

	DIMENSION ARRAY1(3:10), ARRAY2(3,-2:2)
This specifies ARRAY1 as a vector having eight elements with the lower bound of 3 and the upper bound of 10.

ARRAY2 as a matrix of two dimensions having fifteen elements. The first dimension has three elements and the second has five with bounds from -2 to 2.

	CHARACTER B(0:20)*4
sets up an array B with 21 character elements each having a length of four characters. Note that the array has been dimensioned in a type declaration statement and therefore cannot subsequently appear in a DIMENSION statement.


DOUBLE COMPLEX



The DOUBLE COMPLEX statement establishes the data type of a variable by explicitly attaching the name of a variable to a double complex data type. This overrides the implication of data typing by the initial letter of a symbolic name.

Syntax

DOUBLE COMPLEX name [/clist/] [, name] [/clist/]...
name
is the symbolic name of a variable, array, or an array declarator (see the DIMENSION statement for an explanation of array declarators).
clist
is a list of constants that initialize the data, as in a DATA statement.

Description

Type declaration statements may be used to dimension arrays explicitly in the same way as the DIMENSION statement. Type declaration statements must not be labeled. Note: The data type of a symbol may be explicitly declared only once. It is established by type declaration statement, IMPLICIT statement or by predefined typing rules. Explicit declaration of a type overrides any implicit declaration. An IMPLICIT statement overrides predefined typing rules.

The default size of a DOUBLE COMPLEX variable is 16 bytes. With the -Mr8 option, the default size of a DOUBLE COMPLEX variable is also 16 bytes.

Examples

	DOUBLE COMPLEX CURRENT, NEXT

DOUBLE PRECISION



The DOUBLE PRECISION statement establishes the data type of a variable by explicitly attaching the name of a variable to a double precision data type. This overrides the implication of data typing by the initial letter of a symbolic name.

Syntax

DOUBLE PRECISION name [/clist/] [, name] [/clist/]...
name
is the symbolic name of a variable, array, or an array declarator (see the DIMENSION statement for an explanation of array declarators).
clist
is a list of constants that initialize the data, as in a DATA statement.

Description

Type declaration statements may be used to dimension arrays explicitly in the same way as the DIMENSION statement. Type declaration statements must not be labeled. Note: The data type of a symbol may be explicitly declared only once. It is established by type declaration statement, IMPLICIT statement or by predefined typing rules. Explicit declaration of a type overrides any implicit declaration. An IMPLICIT statement overrides predefined typing rules.

The default size of a DOUBLE PRECISION variable is 8 bytes.

Examples

	DOUBLE PRECISION PLONG

DO (Iterative)



The DO statement introduces an iterative loop and specifies the loop control index and parameters.

Syntax

DO [label [,]] i = el, e2 [, e3]
label
labels the last executable statement in the loop (this must not be a transfer of control).
i
is the name of a variable called the DO variable.
e1
is an expression which yields an initial value for i.
e2
is an expression which yields a final value for i.
e3
is an optional expression yielding a value specifying the increment value for i. The default for e3 is 1.

Description

@ If the optional label, label is not included, the DO statement must be terminated by an END DO statement.

The DO loop consists of all the executable statements after the specifying DO statement up to and including the labeled statement, called the terminal statement. The label is optional. If omitted, the terminal statement of the loop is an END DO statement.

@ END DO may be used to terminate the DO loop even if a label is specified.

Before execution of a DO loop, an iteration count is initialized for the loop. This value is the number of times the DO loop is executed, and is

INT((e2-e1+e3)/e3)
If the value obtained is negative or zero that the loop is not executed.

The DO loop is executed first with i taking the value e1, then the value (e1+e3), then the value (e1+e3+e3), etc.

It is possible to jump out of a DO loop and jump back in, as long as the do index variable has not been adjusted.

@ Nested DO loops may share the same labeled terminal statement if required. They may not share an END DO statement.

In a nested DO loop, it is legal to transfer control from an inner loop to an outer loop. It is illegal, however, to transfer into a nested loop from outside the loop.

Example

	DO 100 J = -10,10
DO 100 I = -5,5
100 SUM = SUM + ARRAY (I,J)

DO WHILE @



The DO WHILE statement introduces a logical do loop and specifies the loop control expression.

The DO WHILE statement executes for as long as the logical expression e continues to be true when tested at the beginning of each iteration. If e is false, control transfers to the statement following the loop.

Syntax

DO [label[,]] WHILE expression
The end of the loop is specified in the same way as for an iterative loop, either with a labeled statement or an END DO.
label
labels the last executable statement in the loop (this must not be a transfer of control).
expression
is a logical expression and label.

Description

The logical-expression is evaluated. If it is .FALSE., the loop is not entered. If it is .TRUE., the loop is executed once. Then logical-expression is evaluated again, and the cycle is repeated until the expression evaluates .FALSE..


ELSE



The ELSE statement begins an ELSE block of an IF block and encloses a series of statements that are conditionally executed.

Syntax

IF logical expression THEN
statements
ELSE IF logical expression THEN
statements
ELSE
statements
ENDIF
The ELSE section is optional and may occur only once. Other IF blocks may be nested within the statements section of an ELSE block.

Example

	IF (I.LT.15) THEN
M = 4
ELSE
M=5
ENDIF

ELSE IF



The ELSE IF statement begins an ELSE IF block of an IF block series and encloses statements that are conditionally executed.

Syntax

IF logical expression THEN
statements
ELSE IF logical expression THEN
statements
ELSE
statements
ENDIF
The ELSE IF section is optional and may be repeated any number of times. Other IF blocks may be nested within the statements section of an ELSE IF block.

Example

	IF (I.GT.70) THEN
M=1
ELSE IF (I.LT.5) THEN
M=2
ELSE IF (I.LT.16) THEN
M=3
ENDIF

ENCODE @



The ENCODE statement transfers data between variables or arrays in internal storage and translates that data from internal to character form, according to format specifiers. Similar results can be accomplished using internal files with formatted sequential WRITE statements.

Syntax

ENCODE (c,f,b[,IOSTAT=ios] [,ERR=errs])[list]

c
is an integer expression specifying the number of bytes involved in translation,
f
is the format identifier,
b
is a scalar or array reference for the buffer area receiving formatted data (characters)
ios
is the an integer scalar memory reference which is the input/output status specifier: if this is included, ios becomes defined with zero if no error condition exists or a positive integer when there is an error condition.
errs
an error specifier which takes the form of a statement label of an executable statement in the same program. If an error condition occurs execution continues with the statement specified by errs
list
a list of output items.

END



This END statement terminates a module. It may be the last statement in a compilation or it may be followed by a new module.

Syntax

END

Description

The END statement is executable, and has the same effect as a RETURN statement in a SUBROUTINE or FUNCTION, or the effect of a STOP statement in a PROGRAM module.


END DO @



The END DO statement terminates a DO or DO WHILE loop.

Syntax

END DO

Description

The END DO statement terminates an indexed DO or DO WHILE statement which does not contain a terminal-statement label.

The END DO statement may also be used as a labeled terminal statement if the DO or DO WHILE statement contains a terminal-statement label.


END FILE



When an END FILE statement is executed an endfile record is written to the file as the next record. The file is then positioned after the endfile record. Note that only records written prior to the endfile record can be read later.

Syntax

END FILE u
END FILE ([UNIT=]u, list)
u
is the external unit specifier where u is an integer.
list
contains the optional specifiers as follows:
IOSTAT=ios
an integer scalar memory reference which is the input/output specifier: if this is included in list ios becomes defined with zero if no error condition exists or a positive integer when there is an error condition.
ERR=errs
an error specifier which takes the form of a statement label of an executable statement in the same program. If an error condition occurs execution continues with the statement specified by errs.
A BACKSPACE or REWIND statement must be used to reposition the file after an END FILE statement prior to the execution of any data transfer statement. A file is created if there is an END FILE statement for a file connected but not in existence.

Examples

	END FILE(20)
	END FILE(UNIT=34, IOSTAT=IOERR, ERR=140)

END IF



The END IF statement terminates an IF. ELSE or ELSE IF block.

Syntax

END IF

Description

The END IF statement terminates an IF block. Thre must be a matching block IF statement (at the same IF level) earlier in the same subprogram.


END MAP @



The END MAP statement terminates a MAP declaration.

Syntax

END MAP

Description

See the MAP statement for details.


END STRUCTURE @



The END STRUCTURE statement terminates a STRUCTURE declaration.

Syntax

END STRUCTURE

Description

See the STRUCTURE statement for details.


END UNION @



The END UNION statement terminates a UNION declaration.

Syntax

END UNION

Description

See the UNION statement for details.


ENTRY



The ENTRY statement allows a subroutine or function to have more than one entry point.

Syntax

ENTRY name [(variable, variable...)]
name
is the symbolic name, or entry name, by which the subroutine or function may be referenced.
variable
is a dummy argument. A dummy argument may be a variable name, array name, dummy procedure or, if the ENTRY is in a subroutine, an alternate return arguemnt indicated by an asterisk. If there are no dummy arguments name may optionally be followed by (). There may be more than one ENTRY statement within a subroutine or function, but they must not appear within a block IF or DO loop.

Description

The name of an ENTRY must not be used as a dummy argument in a FUNCTION, SUBROUTINE or ENTRY statement, nor may it appear in an EXTERNAL statement.

Within a function a variable name which is the same as the entry name may not appear in any statement that precedes the ENTRY statement, except in a type statement.

If name is of type character the names of each entry in the function and the function name must be of type character. If the function name or any entry name has a length of (*) all such names must have a length of (*); otherwise they must all have a length specification of the same integer value.

A name which is used as a dummy argument must not appear in an executable statement preceding the ENTRY statement unless it also appears in a FUNCTION, SUBROUTINE or ENTRY statement that precedes the executable statement. Neither must it appear in the expression of a statement function unless the name is also a dummy argument of the statement function, or appears in a FUNCTION or SUBROUTINE statement, or in an ENTRY statement that precedes the statement function statement.

If a dummy argument appears in an executable statement, execution of that statement is only permitted during the execution of a reference to the function or subroutine if the dummy argument appears in the dummy argument list of the procedure name referenced.

When a subroutine or function is called using the entry name, execution begins with the statement immediately following the ENTRY statement. If a function entry has no dummy arguments the function must be referenced by name() but a subroutine entry without dummy arguments may be called with or without the parentheses after the entry name.

An entry may be referenced from any module except the one in which it is defined.

The order, type, number and names of dummy arguments in an ENTRY statement can be different from those used in the FUNCTION, SUBROUTINE or other ENTRY statements in the same module but each reference must use an actual argument list which agrees in order, number and type with the dummy argument list of the corresponding FUNCTION, SUBROUTINE or ENTRY statement. When a subroutine name or an alternate return specifier is used as an actual argument there is no need to match the type.

Entry names within a FUNCTION subprogram need not be of the same data type as the function name, but they all must be consistent within one of the following groups of data types:

If the function is of character data type, all entry names must also have the same length specification as that of the function.

Example

	FUNCTION SUM(TALL,SHORT,TINY)
.
SUM=TALL-(SHORT+TINY)
RETURN
ENTRY SUM1(X,LONG,TALL,WIDE,NARROW)
.
.
SUM1=(X*LONG)+(TALL*WIDE)+NARROW
RETURN

ENTRY SUM2(SHORT,SMALL,TALL,WIDE)
.
.
SUM2=(TALL-SMALL)+(WIDE-SHORT)
RETURN
END
When the calling program calls the function SUM it can do so in one of three ways depending on which ENTRY point is desired.

For example if the call is:

Z=SUM2(LITTLE,SMALL,BIG,HUGE)
the ENTRY point is SUM2.

If the call is:

Z=SUM(T,X,Y)
the ENTRY point is SUM and so on.


EQUIVALENCE



The EQUIVALENCE statement allows two or more named regions of data memory to share the same start address.

Syntax

EQUIVALENCE  (list)[,(list)...]
list
is a set of identifiers (variables, arrays or array elements) which are to be associated with the same address in data memory. The items in a list are separated by commas, and there must be at least two items in each list. When an array element is chosen, the subscripts must be integer constants or integer PARAMETER constants.

Description

@ An array element may be identified with a single subscript in an EQUIVALENCE statement even though the array is defined to be a multidimensional array.

@ Equivalence of character and non-character data is allowed as long as misalignment of non-character data does not occur.

Records and record fields cannot be specified in EQUIVALENCE statements.

The statement can be used to make a single region of data memory have different types, so that for instance the imaginary part of a complex number can be treated as a real value. make arrays overlap, so that the same region of store can be dimensioned in several different ways.

Example

	COMPLEX NUM
REAL QWER(2)
EQUIVALENCE (NUM,QWER(1))
In the above example QWER(1) is the real part of NUM and QWER(2) is the imaginary part. EQUIVALENCE statements are illegal if there is any attempt to make a mapping of data memory inconsistent with its linear layout.


EXTERNAL



The EXTERNAL statement identifies a symbolic name as an external or dummy procedure. This procedure can then be used as an actual argument.

Syntax

EXTERNAL proc [,proc]..
proc
is the name of an external procedure, dummy procedure or block data module. When an external or dummy procedure name is used as an actual argument in a module it must appear in an EXTERNAL statement in that module.

Description

If an intrinsic function appears in an EXTERNAL statement an intrinsic function of the same name cannot then be referenced in the module. A symbolic name can appear only once in all the EXTERNAL statements of a module.


FORMAT



The FORMAT statement specifies format requirements for input or output.

Syntax

label FORMAT (list-items)
list-items
can be any of the following, separated by commas:
Each action of format control depends on the next edit code and the next item in the input/output list where one is used. If an input/output list contains at least one item there must be at least one repeatable edit code in the format specification. An empty format specification () can only be used if no list items are specified; in such a case one input record is skipped or an output record containing no characters is written. Unless the edit code or the format list is preceded by a repeat specification, a format specification is interpreted from left to right. Where a repeat specification is used the appropriate item is repeated the required number of times.

Description

Refer to section 4.4.2, Format Specificatins.

Examples

	     WRITE (6,90) NPAGE
	90   FORMAT('1PAGE NUMBER ',I2,16X,'SALES REPORT, Cont.')
produces:
	     PAGE NUMBER  SALES REPORT, Cont.
The following example shows use of the tabulation specifier T:
	     PRINT 25
25 FORMAT (T41,'COLUMN 2',T21,'COLUMN 1')
produces:
	     COLUMN 1    COLUMN 2
	    DIMENSION A(6)
DO 10 I = 1,6
10 A(I) = 25.
TYPE 100,A
100 FORMAT(' ',F8.2,2PF8.2,F8.2) ! ' '
C ! gives single spacing
produces:
25.00  2500.00  2500.00  2500.00  2500.00  2500.00
Note that the effect of the scale factor continues until another scale factor is used.


FUNCTION



The function statement introduces a module; the statements that follow all apply to the function itself and are laid out in the same order as those of a PROGRAM module.

Syntax

[type] FUNCTION name [*n] ([argument [,argument]...])
type
will explicitly apply a type to the function. If the function is not explicitly typed then the function type is taken from the initial letter and is dictated by the usual default.
name
is the name of the function and must be unique amongst all the module names in the program. name must not clash with any local, COMMON or PARAMETER names.
*n
is the optional length of the data type.
argument
is a symbolic name, starting with a letter and containing only letters and digits. An argument can be of type REAL, INTEGER, DOUBLE PRECISION, CHARACTER, LOGICAL, COMPLEX, or BYTE, etc.

Description

The statements and names in the module apply only to the function, except for subroutine or function references and the names of COMMON blocks. The module must be terminated by an END statement.

A function produces a result; this allows a function reference to appear in an expression, where the result is assumed to replace the actual reference. The symbolic name of the function must appear as a variable in the module. The value of this variable, on exit from the function, is the result of the function. The result is undefined if the variable has not been defined.

The type of a FUNCTION refers to the type of its result.

Recursion is allowed if the -Mrecursive option is used on the command-line.

Examples

	FUNCTION FRED(A,B,C)
REAL X
.
.
END

FUNCTION EMPTY() ! Note parentheses


END PROGRAM FUNCALL
.
.
SIDE=TOTAL(A,B,C)
.
.
END

FUNCTION TOTAL(X,Y,Z)
.
.
END FUNCTION AORB(A,B)
IF(A-B)1,2,3
1 AORB = A
RETURN
2 AORB = B
RETURN
3 AORB = A + B
RETURN
END

GOTO (Assigned)



The assigned GOTO statement transfers control so that the statement identified by the statement label is executed next.

Syntax

GOTO integer-variable-name[[,] (list)]
integer-variable-name
must be defined with the value of a statement label of an executable statement within the same module. This type of definition can only be done by the ASSIGN statement.
list
consists of one or more statement labels attached to executable statements in the same program unit. If a list of statement labels is present, the statement label assigned to the integer variable must be in that list.

Examples

	ASSIGN 50 TO K
GO TO K(50,90)
90 G=D**5
.
.
50 F=R/T

GOTO (Computed)



The computed GOTO statement allows transfer of control to one of a list of labels according to the value of an expression.

Syntax

GOTO (list) [,] expression
list
is a list of labels separated by commas.
expression
selects the label from the list to which to transfer control. Thus a value of 1 implies the first label in the list, a value of 2 implies the second label and so on. An expression value outside the range will result in transfer of control to the statement following the computed GOTO statement.

Example

	READ *, A, B
GO TO (50,60,70)A
WRITE (*, 10) A, B
10 FORMAT (' ', I3, F10.4, 5X, 'A must be 1, 2
+ or 3')
STOP
50 X=A**B ! Come here if A has the value 1
GO TO 100
60 X=(A*56)*(B/3) !Come here if A is 2
GO TO 100
70 X=A*B ! Come here if A has the value 3
100 WRITE (*, 20) A, B, X
20 FORMAT (' ', I3, F10.4, 5X, F10.4)

GOTO (Unconditional)



The GOTO statement unconditionally transfers control to the statement with the label label. The statement label label must be declared within the code of the module containing the GOTO statement and must be unique within that module.

Syntax

GOTO label
label
is a statement label

Example

	TOTAL=0.0
30 READ *, X
IF (X.GE.0) THEN
TOTAL=TOTAL+X
GOTO 30
END IF


IF (Arithmetic)



The arithmetic IF statement transfers control to one of three labeled statements. The statement chosen depends upon the value of an arithmetic expression.

Syntax

IF (arithmetic-expression) label-1, label-2, label-3
Control transfers to label-1, label-2 or label-3 if the result of the evaluation of the arithmetic-expression is less than zero, equal to zero or greater than zero respectively.

Example

IF X 10, 20, 30
if X is less than zero then control is transferred to label 10.

if X equals zero then control is transferred to label 20.

if X is greater than zero then control is transferred to label 30.


IF (Block)



The block IF statement consists of a series of statements that are conditionally executed.

Syntax

IF logical expression THEN
statements
ELSE IF logical expression THEN
statements
ELSE
statements
ENDIF
The ELSE IF section is optional and may be repeated any number of times. Other IF blocks may be nested within the statements section of an IF block.

Example

	IF (I.GT.70) THEN
M=1
ELSE IF (I.LT.5) THEN
M=2
ELSE IF (I.LT.16) THEN
M=3
ENDIF
IF (I.LT.15) THEN
M = 4
ELSE
M=5
ENDIF

IF (Logical)



The logical IF statement executes or does not execute a statement based on the value of a logical expression.

Syntax

IF (logical-expression) statement
logical-expression
is evaluated and if it is true the statement is executed. If it is false statement is not executed and control is passed to the next executable statement.
statement
can be an assignment statement, a CALL statement or a GOTO statement.

Examples

  IF(N .LE. 2) GOTO 27
  IF(HIGH .GT. 1000.0 .OR. HIGH .LT. 0.0) HIGH=1000.0

IMPLICIT



The IMPLICIT statement redefines the implied data type of symbolic names from their initial letter. Without the use of the IMPLICIT statement all names that begin with the letters I,J,K,L,M or N are assumed to be of type integer and all names beginning with any other letters are assumed to be real.

Syntax

	IMPLICIT spec (a[,a]...) [,spec (a[,a]...)]
@	IMPLICIT NONE
spec
is a data type specifier.
a
is an alphabetic specification expressed either as a or a1-a2, specifying an alphabetically ordered range of letters.

Description

IMPLICIT statements must not be labeled.

Symbol names may begin with a dollar sign ($) or underscore (_) character, both of which are of type REAL by default. In an IMPLICIT statement, these characters may be used in the same manner as other characters, but they cannot be used in a range specification.

The IMPLICIT NONE statement specifies that all symbolic names must be explicitly declared, otherwise an error is reported. If IMPLICT NONE is used, no other IMPLICIT can be present.

Examples

	IMPLICIT REAL (L,N)
	IMPLICIT INTEGER (S,W-Z)
	IMPLICIT INTEGER (A-D,$,_)

INCLUDE @



The INCLUDE statement directs the compiler to start reading from another file.

Syntax

INCLUDE 'filename[/[NO]LIST]'
INCLUDE "filename[/[NO]LIST]"
The INCLUDE statement may be nested to a depth of 20 and can appear anywhere within a program unit as long as Fortran's statement-ordering restrictions are not violated.

The qualifiers /LIST and /NOLIST can be used to control whether the include file is expanded in the listing file (if generated).

Note that there is no support for VAX/VMS text libraries or the module_name pathname qualifier that exists in the VAX/VMS version of the INCLUDE statement.

Either single or double quotes may be used.

If the final component of the file pathname is /LIST or /NOLIST, the compiler will assume it is a qualifier, unless an additional qualifier is supplied.

The filename and the /LIST or /NOLISt qualifier may be separated by blanks.

Example

	INCLUDE  '/mypath/list  /list'
This includes a file named /mypath/list and expands it in the listing.


INQUIRE



An INQUIRE statement has two forms and is used to inquire about the current properties of a particular file or the current connections of a particular unit. INQUIRE may be executed before, during or after a file is connected to a unit.

Syntax

INQUIRE (FILE=filename, list)  
INQUIRE ([UNIT=]unit,list)
list of specifiers is as follows:
ACCESS=
acc
acc
a character scalar memory reference which specifies the access method for file connection as either DIRECT or SEQUENTIAL; the default is SEQUENTIAL
BLANK=
blnk
blnk
a character scalar memory reference taking the value NULL or ZERO. NULL causes all blank characters in numeric formatted input fields to be ignored with the exception of an all blank field which has a value of zero. ZERO causes all blanks other than leading blanks to be treated as zeros. This specifier must only be used when a file is connected for formatted input/output
DIRECT=
dir
dir
a character scalar memory reference which takes the value YES if DIRECT is one of the allowed access methods for the file, NO if not and UNKNOWN if it is not known if DIRECT is included
ERR=
errs
errs
an error specifier which takes the form of a statement label of an executable statement in the same program. If an error condition occurs execution continues with the statement specified by errs
EXIST=
ex
ex
a logical variable or logical array element which becomes .TRUE. if there is a file/unit with the specified name or .FALSE. otherwise
FORM=
fm
fm
a character scalar memory reference specifying whether the file is being connected for FORMATTED or UNFORMATTED output; the default is UNFORMATTED
FORMATTED=
fmt
fmt
a character scalar memory reference which takes the value YES if FORMATTED is one of the allowed access methods for the file, NO if not and UNKNOWN if it is not known if FORMATTED is included
IOSTAT=
ios
ios
is the an integer scalar memory reference which is the input/output specifier: if this is included in list, ios is defined with 0 if no error condition exists or a positive integer when there is an error.
NAME=
fn
fn
a character scalar memory reference which is assigned the name of the file when the file has a name, otherwise it is undefined
NAMED=
nmd
nmd
a logical scalar memory reference which becomes .TRUE. if the file has a name, otherwise it becomes .FALSE.
NEXTREC=
nr
nr
an integer scalar memory reference which is assigned the value n+1, where n is the number of the record read or written. It takes the value 1 if no records have been read or written. If the file is not connected or its position is indeterminate nr is undefined
NUMBER=
num
num
an integer scalar memory reference or integer array element assigned the value of the external unit number of the currently connected unit. It becomes undefined if no unit is connected
OPENED=
od
od
a logical scalar memory reference which becomes .TRUE. if the file/unit specified is connected as appropriate
RECL=
rcl
rcl
an integer scalar memory reference defining the record length in a file connected for direct access and is the number of characters when formatted input/output is specified. This specifier must only be given when a file is connected for direct access
SEQUENTIAL=
seq
seq
a character scalar memory reference which is assigned the value YES if SEQUENTIAL is included in the set of allowed access methods, NO if SEQUENTIAL is not included and UNKNOWN if it cannot be determined whether or not SEQUENTIAL is included
UNFORMATTED=
unf
unf
a character scalar memory reference which takes the value YES if UNFORMATTED is one of the allowed access methods for the file, NO if not and UNKNOWN if it is not known if UNFORMATTED is included

Description

When an INQUIRE by file statement is executed the following specifiers will only be assigned values if the file name is acceptable:

nmd, fn, seq, dir, fmt and unf. num is defined, and acc, fm, rcl, nr and blnk may become defined only if od is defined as .TRUE..

When an INQUIRE by unit statement is executed the specifiers num, nmd, fn, acc, seq, dir, fm, fmt, unf, rcl, nr and blnk are assigned values provided that the specified unit exists and a file is connected to that unit. Should an error condition occur during the execution of an INQUIRE statement all the specifiers except ios become undefined.


INTEGER



The INTEGER statement establishes the data type of a variable by explicitly attaching the name of a variable to an integer data type. This overrides the implication of data typing by the initial letter of a symbolic name.

Syntax

INTEGER [*n] [,] name [*n] [dimensions] [/clist/] [, name [*n][dimensions] [/clist/]]...
n
is an optional size specification.
name
is the symbolic name of a variable, array, or an array declarator (see the DIMENSION statement for an explanation of array declarators).
clist
is a list of constants that initialize the data, as in a DATA statement.

Description

Integer type declaration statements may be used to dimension arrays explicitly in the same way as the DIMENSION statement. INTEGER statements must not be labeled. Note: The data type of a symbol may be explicitly declared only once. It is established by type declaration statement, IMPLICIT statement or by predefined typing rules. Explicit declaration of a type overrides any implicit declaration. An IMPLICIT statement overrides predefined typing rules.

The default size of an INTEGER variable is 4 bytes. With the -Mnoi4 option, the default size of an INTEGER variable is 2 bytes.

Example

	INTEGER TIME, SECOND, STORE  (5,5)

INTRINSIC



An INTRINSIC statement identifies a symbolic name as an intrinsic function and allows it to be used as an actual argument.

Syntax

INTRINSIC func [,func]
func
is the name of an intrinsic function such as SIN, COS, etc.

Description

Do not use any of the following functions in INTRINSIC statements:

INT, IFIX, IDINT, FLOAT, SNGL, REAL, DBLE, CMPLX, ICHAR, CHAR LGE, LGT, LLE, LLT MAX, MAX0, AMAX1, DMAX1, AMAX0, MAX1, MIN, MIN0, AMIN1, DMIN1, AMIN0, MIN1

When a specific name of an intrinsic function is used as an actual argument in a module it must appear in an INTRINSIC statement in that module. If the name used in an INTRINSIC statement is also the name of a generic intrinsic function, it retains its generic properties. A symbolic name can appear only once in all the INTRINSIC statements of a module and cannot be used in both an EXTERNAL and INTRINSIC statement in a module.

The following example illustrates the use of INTRINSIC and EXTERNAL:

	EXTERNAL MYOWN
INTRINSIC SIN, COS
.
.
CALL TRIG (ANGLE,SIN,SINE)
.
CALL TRIG (ANGLE,MYOWN,COTANGENT)
.
CALL TRIG (ANGLE,COS,SINE) SUBROUTINE TRIG (X,F,Y)
Y=F(X)
RETURN
END
	FUNCTION MYOWN
MYOWN=COS(X)/SIN(X)
RETURN
END
In this example, when TRIG is called with a second argument of SIN or COS the function reference F(X) references the intrinsic functions SIN and COS; however when TRIG is called with MYOWN as the second argument F(X) references the user function MYOWN.


LOGICAL



The LOGICAL statement establishes the data type of a variable by explicitly attaching the name of a variable to an integer data type. This overrides the implication of data typing by the initial letter of a symbolic name.

Syntax

LOGICAL [*n] [,] name [*n] [dimensions] [/clist/][, name] [*n][dimensions] [/clist/]...
n
is an optional size specification.
name
is the symbolic name of a variable, array, or an array declarator (see the DIMENSION statement for an explanation of array declarators).
clist
is a list of constants that initialize the data, as in a DATA statement.

Description

Integer type declaration statements may be used to dimension arrays explicitly in the same way as the DIMENSION statement. Type declaration statements must not be labeled. Note: The data type of a symbol may be explicitly declared only once. It is established by type declaration statement, IMPLICIT statement or by predefined typing rules. Explicit declaration of a type overrides any implicit declaration. An IMPLICIT statement overrides predefined typing rules.

The default size of an LOGICAL variable is 4 bytes. With the -Mnoi4 option, the default size of an LOGICAL variable is 2 bytes.

Example

	LOGICAL TIME, SECOND, STORE  (5,5)

MAP @



A union declaration is initiated by a UNION statement and terminated by an END UNION statement. Enclosed within these statements are one or more map declarations, initiated and terminated by MAP and END MAP statements, respectively. Each unique field or group of fields is defined by a separate map declaration.

Syntax

MAP
field_declaration
[field_declaration]
...
[field_declaration]
END MAP
field_declaration
is a structure declaration or RECORD statement contained within a union declaration, a union declaration contained within a union declaration, or the declaration of a typed data field within a union.

Description

Data can be initialized in field declaration statements in union declarations. Note, however, it is illegal to initialize multiple map declarations in a single union.

The size of the shared area for a union declaration is the size of the largest map defined for that union. The size of a map is the sum of the sizes of the field(s) declared within it plus the space reserved for alignment purposes.

Manipulating data using union declarations is similar to what happens using EQUIVALENCE statements. However, union declarations are probably more similar to union declarations for the language C. The main difference is that the language C requires one to associate a name with each map (union). Fortran field names must be unique within the same declaration nesting level of maps.

Example

The following is an example of RECORD, STRUCTURE and UNION usage. The size of each element of the recarr array would be the size of typetag (4 bytes) plus the size of the largest MAP - the employee map (24 bytes).

STRUCTURE /account/
INTEGER typetag ! Tag to determine defined map.
UNION
MAP ! Structure for an employee
CHARACTER*12 ssn ! Social Security Number
REAL*4 salary
CHARACTER*8 empdate ! Employment date
END MAP
MAP ! Structure for a customer
INTEGER*4 acct_cust
REAL*4 credit_amt
CHARACTER*8 due_date
END MAP
MAP ! Structure for a supplier
INTEGER*4 acct_supp
REAL*4 debit_amt
BYTE num_items
BYTE items(12) ! Items supplied
END MAP
END UNION
END STRUCTURE RECORD /account/ recarr(1000)

NAMELIST @



The NAMELIST statement allows for the definition of namelist groups for namelist-directed I/O.

Syntax

NAMELIST /group-name/ namelist [[,] /group-name/ namelist ]...
group-name
is the name of the namelist group.
namelist
is the list of variables in the namelist group.

Example

In the following example a named group PERS consits of a name, an account, and a value.

	CHARACTER*12  NAME
INTEGER*$ ACCOUNT
REAL*4 VALUE
NAMELIST /PERS/ NAME, ACCOUNT, VALUE

OPEN



The OPEN statement can be used to do the following: connect an existing file to a unit; create and connect a file to a unit; create a file that is preconnected; change certain specifiers of a connection between a file and a unit

Syntax

OPEN ( list )
list
must contain exactly one unit specifier of the form:
[UNIT=] u
where the UNIT= is optional and the external unit specifier u is an integer.

In addition list may contain one of each of the following specifiers in any order.

ACCESS=
acc
acc
is a character expression specifying the access method for file connection as either DIRECT or SEQUENTIAL - the default is SEQUENTIAL.
BLANK=
blnk
blnk
is a character expression which takes the value 'NULL' or 'ZERO': 'NULL' causes all blank characters in numeric formatted input fields to be ignored with the exception of an all blank field which has a value of zero. 'ZERO' causes all blanks other than leading blanks to be treated as zeros. The default is 'NULL.' This specifier must only be used when a file is connected for formatted input/output.
FORM=
fm
fm
is a character expression specifying whether the file is being connected for 'FORMATTED' or 'UNFORMATTED' input/output and is 'FORMATTED' by default.
ERR=
errs
errs
an error specifier which takes the form of a statement label of an executable statement in the same program. If an error condition occurs execution continues with the statement specified by errs.
FILE=
fin
fin
is a character expression whose value is the file name to be connected to the specified unit.
IOSTAT=
ios
ios
input/output status specifier where ios is an integer scalar memory reference: if this is included in list, ios becomes defined with 'ZERO' if no error condition exists or a positive integer when there is an error condition.
RECL=
rl
rl
is an integer expression defining the record length in a file connected for direct access and is the number of characters when formatted input/output is specified. This specifier must only be given when a file is connected for direct access.
STATUS=
sta
sta
is a character expression whose value can be: "NEW", "OLD", "SCRATCH" or "UNKNOWN". When "OLD" or "NEW" is specified a file specifier must be given. "SCRATCH" must not be used with a named file. The default status is UNKNOWN which specifies that the file's existence is unknown, which limits the error checking when opening the file.. With status "OLD", the file must exist or an error is reported. With status "NEW, the file is created, if the file exists, as error is reported. Status "SCRATCH specifies that the file is removed when closed.

Description

The record length, RECL=, must be specified if a file is connected for direct access and optionally one of each of the other specifiers may be used. RECL is ignored if the access method is sequential.

The unit specified must exist and once connected by an OPEN statement can be referenced in any module of the executable program. If a file is connected to a unit it cannot be connected to a different unit by the OPEN statement.

If a unit is connected to an existing file, execution of an OPEN statement for that file is allowed. Where FILE= is not specified the file to be connected is the same as the file currently connected. If the file specified for connection to the unit does not exist but is the same as a preconnected file, the properties specified by the OPEN statement become part of the connection. However, if the file specified is not the same as the preconnected file this has the same effect as the execution of a CLOSE statement without a STATUS= specifier immediately before the execution of the OPEN statement. When the file to be connected is the same as the file already connected only the BLANK= specifier may be different from the one currently defined.

Example

In the following example a new file, BOOK, is created and connected to unit 12 for direct formatted input/output with a record length of 98 characters. Numeric values will have blanks ignored and E1 will be assigned some positive value if an error condition exists when the OPEN statement is executed; execution will then continue with the statement labeled 20. If no error condition pertains, E1 is assigned the value zero (0) and execution continues with the next statement.

	 OPEN( 12, IOSTAT=E1, ERR=20, FILE='BOOK',
1BLANK='NULL', ACCESS='DIRECT', RECL=98,
1FORM='FORMATTED',STATUS='NEW')

Environment Variables

For an OPEN statement which does not contain the FILE= specifier, an environment variable may be used to specify the file to be connected to the unit. If the environment variable FORddd exists, where ddd is a 3 digit string whose value is the unit, the environment variable's value is the name of the file to be opened.

VAX/VMS Fortran

VAX/VMS introduces a number of extensions to the OPEN statement. Many of these relate only to the VMS file system and are not supported (e.g., KEYED access for indexed files). The following keywords for the OPEN statement have been added or augmented as shown below. Refer to Programming in VAX FORTRAN for additional details on these keywords.

ACCESS
The value of 'APPEND' will be recognized and implies sequential access and positioning after the last record of the file. Opening a file with append access means that each appended record is written at the end of the file.
ASSOCIATEVARIABLE
This new keyword specifies an INTEGER*4 integer scalar memory reference which is updated to the next sequential record number after each direct access I/O operation. Only for direct access mode.
DISPOSE and DISP
These new keywords specify the disposition for the file after it is closed. 'KEEP' or 'SAVE' is the default on anything other than STATUS='SCRATCH' files. 'DELETE' indicates that the file is to be removed after it is closed. The PRINT and SUBMIT values are not supported.
NAME
This new keyword is a synonym for FILE.
READONLY
This new keyword specifies that an existing file can be read but prohibits writing to that file. The default is read/write.
RECL=len
The record length given is interpreted as number of words in a record if the runtime environment parameter FTNOPT is set to "vaxio". This simplifies the porting of VAX/VMS programs. The default is that len is given in number of bytes in a record.
TYPE
This keyword is a synonym for STATUS.

OPTIONS @



The OPTIONS statement confirms or overrides certain compiler command-line options.

Syntax

OPTIONS /option [/option ...]
Table 3.1 shows what options are available for the OPTIONS statement.

Option

Action Taken

CHECK=ALL
Enable array bounds checking
CHECK=[NO]OVERFLOW
None (recognized but ignored)
CHECK=[NO]BOUNDS
(Disable) Enable array bounds checkinng
CHECK=[NO]UNDERFLOW
None
CHECK=NONE
Disable array bounds checking
NOCHECK
Disable array bounds checking
[NO]EXTEND_SOURCE
(Disable) Enable the -Mextend option
[NO]F77
(Disable) Enable the -Mstandard option
[NO]G_FLOATING
None
[NO]I4
(Disable) Enable the -Mi4 option
[NO]RECURSIVE
(Disable) Enable the -Mrecursive option
[NO]REENTRANT
(Enable) Disable optimizations that may result in code that is not reentrant.
[NO]STANDARD
(Disable) Enable the -Mstandard option

The following restrictions apply to the OPTIONS statement:


PARAMETER



The PARAMETER statement gives a symbolic name to a constant.

Syntax

PARAMETER (name = expression[,name = expression...] )
expression
is an arithmetic expression formed from constant or PARAMETER elements using the arithmetic operators + - * />. The usual precedence order can be changed by using parentheses. expression may include a previously defined PARAMETER.

Examples

	PARAMETER ( PI = 3.142 )
	PARAMETER ( INDEX = 1024 )
	PARAMETER ( INDEX3 = INDEX * 3 )
The following VAX/VMS extensions to the PARAMETER statement are fully supported: The form of the alternative PARAMETER statement is:
	PARAMETER p=c [,p=c]...
where p is a symbolic name and c is a constant, symbolic constant, or a compile time constant expression.


PAUSE



The PAUSE statement stops the program's execution.

Syntax

PAUSE [character-expression | digits ]
The PAUSE statement stops the program's execution. The program may be restarted later and execution will then continue with the statement following the PAUSE statement.


POINTER @



The POINTER statement declares a scalar variable to be a pointer variable (of type INTEGER), and another variable to be its pointer-based variable.

Syntax

POINTER (p1, v1) [, (p2, v2) ...]
v1 and v2
are pointer-based variables. A pointer-based variable can be of any type, including STRUCTURE. A pointer-based variable can be dimensioned in a separate type, in a DIMENSION statement, or in the POINTER statement. The dimension expression may be adjustable, where the rules for adjustable dummy arrays regarding any variables which appear in the dimension declarators apply.
p1 and p2
are the pointer variables corresponding to v1 and v2. A pointer variable may not be an array. The pointer is an integer variable containing the address of a pointer-based variable. The storage located by the pointer variable is defined by the pointer-based variable (for example, array, data type, etc.). A reference to a pointer-based variable appears in Fortran statements like a normal variable reference (for example, a local variable, a COMMON block variable, or a dummy variable). When the based variable is referenced, the address to which it refers is always taken from its associated pointer (that is, its pointer variable is dereferenced).
The pointer-based variable does not have an address until its corresponding pointer is defined. The pointer is defined in one of the following ways:

Example

	REAL XC(10)
COMMON IC, XC
POINTER (P, I)
POINTER (Q, X(5)) P = LOC(IC)
I = 0 ! IC gets 0 P = LOC(XC)
Q = P + 20 ! same as LOC(XC(6))
X(1) = 0 ! XC(6) gets 0 ALLOCATE (X) ! Q locates a dynamically
! allocated memory area

Restrictions

The following restrictions apply to the POINTER statement:


PRINT



The PRINT statement is a data transfer output statement.

Syntax

PRINT format-identifier [, iolist]
or
@	PRINT namelist-group
format-identifier
a label of a format statement or a variable containing a format string.
iolist
(output list) must either be one of the items in an input list or any other expression. However a character expression involving concatenation of an operand of variable length cannot be included in an output list unless the operand is the symbolic name of a constant.
namelist-group
the name of the namelist group.

Description

When a PRINT statement is executed the following operations are carried out : data is transferred to the standard output device from the items specified in the output list and format specification.[*] The data are transferred between the specified destinations in the order specified by the input/output list. Every item whose value is to be transferred must be defined.


PROGRAM



The program statement specifies the entry point for the linked Fortran program.

Syntax

PROGRAM [name]
name
is optional; if supplied it becomes the name of the program module and must not clash with any other names used in the program. If it is not supplied, a default name is used.

Description

The program statement specifies the entry point for the linked Fortran program. An END statement terminates the program.

Example

	PROGRAM MYOWN
REAL MEAN, TOTAL
.
CALL TRIG(A,B,C,MEAN)
.
END

READ



The READ statement is the data transfer input statement.

Syntax

    READ  ([unit=] u [,FMT=] format-identifier [,control-information] [iolist]
    READ   format-identifier [,iolist]
@   READ   ([unit=] u, [NML=] namelist-group  [,control-information])
format-identifier
a label of a format statement or a variable containing a format string.
control-information
is an optional control specification which can be any of the following:
[,IOSTAT=
ios]
ios
is an integer variable or array element. ios becomes defined with 0 if no error occurs, and a positive integer when there is an error.
[,REC=
rn]
rn
is a record number to read and must be a positive integer. This is only used for direct access files.
[,END=
s]
s
is an executable statement label for the statement used for processing an end of file condition.
[,ERR=
s]
s
is an executable statement label for the statement used for processing an error condition.
iolist
(input list) must either be one of the items in an input list or any other expression.

Description

When a READ statement is executed the following operations are carried out : data is transferred from the standard input device to the items specified in the input and format specification.[*] The data are transferred between the specified destinations in the order specified by the input/output list. Every item whose value is to be transferred must be defined.

Example

	READ(2,110) I,J,K
 110	FORMAT(I2, I4, I3)


REAL



The REAL statement establishes the data type of a variable by explicitly attaching the name of a variable to a data type. This overrides the implication of data typing by the initial letter of a symbolic name.

Syntax

REAL [*n] name [*n] [dimensions] [/clist/] [, name] [*n] [dimensions][/clist/]...
n
is an optional size specification.
name
is the symbolic name of a variable, array, or an array declarator (see the DIMENSION statement below for an explanation of array declarators).
clist
is a list of constants that initialize the data, as in a DATA statement.

Description

The REAL type declaration statements may be used to dimension arrays explicitly in the same way as the DIMENSION statement. Type declaration statements must not be labeled. Note: The data type of a symbol may be explicitly declared only once. It is established by type declaration statement, IMPLICIT statement or by predefined typing rules. Explicit declaration of a type overrides any implicit declaration. An IMPLICIT statement overrides predefined typing rules.

The default size of a REAL variable is 4 bytes. With the -Mr8 option, the default size of an REAL variable is 8 bytes.

Example

	REAL KNOTS

RECORD @



The RECORD statement defines a user-defined aggregate data item.

Syntax

RECORD /structure_name/record_namelist
[,/structure_name/record_namelist]
... [,/structure_name/record_namelist] END RECORD
structure_name
is the name of a previously declared structure.
record_namelist
is a list of one or more variable or array names separated by commas.

Description

You create memory storage for a record by specifying a structure name in the RECORD statement. You define the field values in a record either by defining them in the structure declaration or by assigning them with executable code.

You can access individual fields in a record by combining the parent record name, a period (.), and the field name (for example, recordname.fieldname). For records, a scalar reference means a reference to a name that resolves to a single typed data item (for example, INTEGER), while an aggregate reference means a reference that resolves to a structured data item.

Scalar field references may appear wherever normal variable or array elements may appear with the exception of the COMMON, SAVE, NAMELIST, DATA and EQUIVALENCE statements. Aggregate references may only appear in aggregate assignment statements, unformatted I/O statements, and as parameters to subprograms.

Records are allowed in COMMON and DIMENSION statements.

Example

	STRUCTURE /PERSON/    ! Declare a structure to define a person
INTEGER ID
LOGICAL LIVING
CHARACTER*5 FIRST, LAST, MIDDLE
INTEGER AGE
END STRUCTURE
! Define population to be an array where each element is of
! type person. Also define a variable, me, of type person.
RECORD /PERSON/ POPULATION(2), ME
...
ME.AGE = 34 ! Assign values for the variable me to
ME.LIVING = .TRUE. ! some of the fields.
ME.FIRST = 'Steve'
ME.ID = 542124822
...
POPULATION(1).LAST = 'Jones' ! Assign the "LAST" field of
! element 1 of array population.
POPULATION(2) = ME ! Assign all the values of record
! "ME" to the record population(2)

REDIMENSION @



The REDIMENSION statement dynamically defines the bounds of a deferred-shape array. After a REDIMENSION statement, the bounds of the array become those supplied in the statement, until another such statement is encountered.

Syntax

REDIMENSION name ([lb:]ub[,[lb:]ub]...) 					[,name([lb:]ub[,[lb:]ub]...)]...

Where:
name
is the symbolic name of an array.
[lb:]ub
is a dimension declarator specifying the bounds for a dimension (the lower bound lb and the upper bound ub). lb and ub must be integers with ub greater than lb. The lower bound lb is optional; if it is not specified, it is assumed to be 1. The number of dimension declarations must be the same as the number of dimensions in the array.

Example

	REAL A(:, :)
POINTER (P, A)
P = malloc(12 * 10 * 4)
REDIMENSION A(12, 10)
A(3, 4) = 33.

RETURN



The RETURN statement causes a return to the statement following a CALL when used in a subroutine, and to within the relevant arithmetic expression when used in a function.

Syntax

RETURN

RETURN alternate Statement

The alternate RETURN statement takes the following form:

RETURN expression
expression
expression is converted to integer if necessary (expression may be of type integer or real). If the value of iexpression is greateer than or equal to 1 and less than or equal to the number of of asterisks in the SUBROUTINE or subroutine ENTRY statement then the value of expression identifies the nth asterisk in the actual argument list and control is returned to that statement.

Example

	SUBROUTINE FIX (A,B,*,*,C)

40 IF (T) 50, 60, 70
50 RETURN
60 RETURN 1
70 RETURN 2
END
PROGRAM FIXIT
CALL FIX(X, Y, *100, *200, S)
WRITE(*,5) X, S ! Come here if (T) < 0
STOP
100 WRITE(*, 10) X, Y ! Come here if (T) = 0
STOP
200 WRITE(*,20) Y, S ! Come here if (T) > 0

REWIND



The REWIND statement positions the file at its beginning. The statement has no effect if the file is already positioned at the start or if the file is connected but does not exist.

Syntax

REWIND  unit
REWIND (unit,list)
unit
is an integer value which is the external unit.
list
contains the optional specifiers as follows:
IOSTAT=
ios
ios
an integer scalar memory reference which is the input/output specifier: if this is included in list, ios becomes defined with zero if no error condition exists or with a positive integer if there is an error condition
ERR=
errs
errs
an error specifier which takes the form of a statement label of an executable statement in the same program. If an error condition occurs execution continues with the statement specified by errs

Examples

	REWIND 5
	REWIND(2, ERR=30)
	REWIND(3, IOSTAT=IOERR)

SAVE



The SAVE statement retains the definition status of an entity after a RETURN or END statement in a subroutine or function has been executed.

Syntax

SAVE [v [, v ]...]
v
name of array, variable, or common block (enclosed in slashes)

Description

Using a common-block name, preceded and followed by a slash, ensures that all entities within that COMMON block are saved. SAVE may be used without a list, in which case all the allowable entities within the module are saved (this has the same effect as using the -Msave command-line option). Dummy arguments, names of procedures and names of entities within a common block may not be specified in a SAVE statement. Use of the SAVE statement with local variables ensures the values of the local varialbes are retained for the next invocation of the SUBROUTINE or FUNCTION. Within a main program the SAVE statement is optional and has no effect.

When a RETURN or END is executed within a subroutine or function, all entities become undefined with the exception of:

Example

	PROGRAM SAFE
.
CALL KEEP
.
SUBROUTINE KEEP
COMMON /LIST/ TOP, MIDDLE
INTEGER LOCAL1.
.
SAVE /LIST/, LOCAL1

STOP



The STOP statement stops the program's execution and precludes any further execution of the program.

Syntax

STOP [character-expression | digits ]

STRUCTURE @



The STRUCTURE statement defines an aggregate data type.

Syntax

STRUCTURE [/structure_name/][field_namelist]
field_declaration
[field_declaration]
... [field_declaration]
END STRUCTURE
structure_name
is unique and is used both to identify the structure and to allow its use in subsequent RECORD statements.
field_namelist
is a list of fields having the structure of the associated structure declaration. A field_namelist is allowed only in nested structure declarations.
field_declaration
can consist of any combination of substructure declarations, typed data declarations, union declarations or unnamed field declarations.

Description

Fields within structures conform to machine-dependent alignment requirements. Alignment of fields also provides a C-like "struct" building capability and allows convenient inter-language communications. Note that aligning of structure fields is not supported by VAX/VMS Fortran.

Field names within the same declaration nesting level must be unique, but an inner structure declaration can include field names used in an outer structure declaration without conflict. Also, because records use periods to separate fields, it is not legal to use relational operators (for example, .EQ., .XOR.), logical constants (.TRUE. or .FALSE.), or logical expressions (.AND., .NOT., .OR.) as field names in structure declarations.

Fields in a structure are aligned as required by hardware and a structure's storage requirements are therefore machine-dependent. Note that VAX/VMS Fortran does no padding. Because explicit padding of records is not necessary, the compiler recognizes the %FILL intrinsic, but performs no action in response to it.

Data initialization can occur for the individual fields.

The UNION and MAP statements are supported.

The following is an example of record and structure usage.

STRUCTURE /account/
INTEGER typetag ! Tag to determine defined map.
UNION
MAP ! Structure for an employee
CHARACTER*12 ssn ! Social Security Number
REAL*4 salary
CHARACTER*8 empdate ! Employment date
END MAP
MAP ! Structure for a customer
INTEGER*4 acct_cust
REAL*4 credit_amt
CHARACTER*8 due_date
END MAP
MAP ! Structure for a supplier
INTEGER*4 acct_supp
REAL*4 debit_amt
BYTE num_items
BYTE items(12) ! Items supplied
END MAP
END UNION
END STRUCTURE RECORD /account/ recarr(1000)

SUBROUTINE



The SUBROUTINE statement introduces a module. The statements that follow should be laid out in the same order as a PROGRAM module.

Syntax

SUBROUTINE name [(argument[,argument...])]
name
is the name of the subroutine being declared and must be unique amongst all the subroutine and function names in the program. name should not clash with any local, COMMON, PARAMETER or ENTRY names.
argument
is a symbolic name, starting with a letter and containing only letters and digits. The type of argument can be REAL, INTEGER, DOUBLE PRECISION, CHARACTER, COMPLEX, or BYTE, etc.

Description

The SUBROUTINE module must be terminated by an END statement. The statements and names in the module only apply to the subroutine except for subroutine or function references and the names of COMMON blocks. Dummy arguments may be specified as * which indicates that the SUBROUTINE contains alternate returns.

Recursion is allowed with the -Mrecursive option.

Example

	SUBROUTINE STAR(A,B,C,*,*)  
Note the dummy arguments represented by the two *s.
	IF (ANY) THEN
A=45
B=36.33
C=0
RETURN 1
ELSE
C=100
RETURN 2
END IF
END PROGRAM SHOWME
.
.
CALL STAR(R,S,T,*30,*40)
.
.
30 WRITE(*,10) R,S ! Come here if RETURN 1
.
.
40 WRITE(*,20) T ! Come here if RETURN 2 .

THEN



The THEN statement is part of a block IF statement and surrounds a series of statements that are conditionally executed.

Syntax

IF logical expression THEN
statements
ELSE IF logical expression THEN
statements
ELSE
statements
ENDIF
The ELSE IF section is optional and may be repeated any number of times. Other IF blocks may be nested within the statements section of an IF block.

Example

	IF (I.GT.70) THEN
M=1
ELSE IF (I.LT.5) THEN
M=2
ELSE IF (I.LT.16) THEN
M=3
ENDIF
IF (I.LT.15) THEN
M = 4
ELSE
M=5
ENDIF

TYPE @



The TYPE statement has the same syntax and effect as the PRINT statement. Refer to the PRINT entry for a description of its syntax and a description.


UNION @



A union declaration is a multistatement declaration defining a data area that can be shared intermittently during program execution by one or more fields or groups of fields. It declares groups of fields that share a common location within a structure. Each group of fields within a union declaration is declared by a map declaration, with one or more fields per map declaration.

Syntax

UNION
map_declaration
[map_declaration]
...
[map_declaration]
END UNION
The format of the map_declaration is as follows:
MAP
field_declaration
[field_declaration]
...
[field_declaration]
END MAP
field_declaration
is a structure declaration or RECORD statement contained within a union declaration, a union declaration contained within a union declaration, or the declaration of a typed data field within a union.

Description

Union declarations are used when one wants to use the same area of memory to alternately contain two or more groups of fields. Whenever one of the fields declared by a union declaration is referenced in a program, that field and any other fields in its map declaration become defined. Then, when a field in one of the other map declarations in the union declaration is referenced, the fields in that map declaration become defined, superseding the fields that were previously defined.

A union declaration is initiated by a UNION statement and terminated by an END UNION statement. Enclosed within these statements are one or more map declarations, initiated and terminated by MAP and END MAP statements, respectively. Each unique field or group of fields is defined by a separate map declaration. The format of a UNION statement is as follows:

Data can be initialized in field declaration statements in union declarations. Note, however, it is illegal to initialize multiple map declarations in a single union.

The size of the shared area for a union declaration is the size of the largest map defined for that union. The size of a map is the sum of the sizes of the field(s) declared within it plus the space reserved for alignment purposes.

Manipulating data using union declarations is similar to what happens using EQUIVALENCE statements. However, union declarations are probably more similar to union declarations for the language C. The main difference is that the language C requires one to associate a name with each map (union). Fortran field names must be unique within the same declaration nesting level of maps.

The following is an example of RECORD, STRUCTURE and UNION usage. The size of each element of the recarr array would be the size of typetag (4 bytes) plus the size of the largest MAP - the employee map (24 bytes).

STRUCTURE /account/
INTEGER typetag ! Tag to determine defined map.
UNION
MAP ! Structure for an employee
CHARACTER*12 ssn ! Social Security Number
REAL*4 salary
CHARACTER*8 empdate ! Employment date
END MAP
MAP ! Structure for a customer
INTEGER*4 acct_cust
REAL*4 credit_amt
CHARACTER*8 due_date
END MAP
MAP ! Structure for a supplier
INTEGER*4 acct_supp
REAL*4 debit_amt
BYTE num_items
BYTE items(12) ! Items supplied
END MAP
END UNION
END STRUCTURE RECORD /account/ recarr(1000)

VOLATILE @



The VOLATILE statement inhibits all optimizations on the variables, arrays and common blocks that it identifies.

Syntax

VOLATILE nitem [, nitem ...]
nitem
is the name of a variable, an array, or a common block enclosed in slashes.

Description

If nitem names a common block, all members of the block are volatile. The volatile attribute of a variable is inherited by any direct or indirect equivalences, as shown in the example.

Example

	COMMON /COM/ C1, C2
VOLATILE /COM/, DIR ! /COM/ and DIR are volatile
EQUIVALENCE (DIR, X) ! X is volatile
EQUIVALENCE (X, Y) ! Y is volatile

WRITE



The WRITE statement is a data transfer output statement.

Syntax

    WRITE  ([unit=] u, format-identifier [,control-information) [iolist]
@   WRITE  ([unit=] u, [NML=] namelist-group  [,control-information])
format-identifier
a label of a format statement or a variable containing a format string.
control-information
is an optional control specification which can be any of the following:
[,IOSTAT=
ios]
ios
is an integer variable or array element. ios becomes defined with 0 if no error occurs, and a positive integer when there is an error.
[,REC=
rn]
rn
is a record number to read and must be a positive integer. This is only used for direct access files.
[,ERR=
s]
s
is an executable statement label for the statement used for processing an error condition.
iolist
(output list) must either be one of the items in an input list or any other expression. However a character expression involving concatenation of an operand of variable length cannot be included in an output list unless the operand is the symbolic name of a constant.

Description

When a WRITE statement is executed the following operations are carried out: data is transferred to the standard output device from the items specified in the output list and format specification.[*] The data are transferred between the specified destinations in the order specified by the input/output list. Every item whose value is to be transferred must be defined.

Example

	   WRITE (6,90) NPAGE
	90 FORMAT('1PAGE NUMBER ',I2,16X,'SALES REPORT, Cont.')

[*] if an asterisk (*) is used instead of a format identifier, the list-directed formatting rules apply.

[*] If an asterisk (*) is used instead of a format identifier, the list-directed formatting rules apply.

[*] if an asterisk (*) is used instead of a format identifier, the list-directed formatting rules apply.


<< >> Title Contents Index Home Help