Skip to content. Skip to navigation

ICTP Portal

Sections
You are here: Home Manuals on-line PGI Compiler pghpf_ref PGHPF Workstation Reference Manual - 3 Fortran Statements
Personal tools
Document Actions

PGHPF Workstation Reference Manual - 3 Fortran Statements

<< << " border=0> >> > " border=0> 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.

At the top of each reference page is an indication of the origin of the statement. Categories of origin are: 77 for Fortran 77 statements that are essentially unchanged from the original Fortran 77 standard. The heading 90, indicates the statement is either new for Fortran 90, or significantly changed in Fortran 90 from its original Fortran 77 definition. The heading HPF, indicates that the statement has its origin in the HPF standard. The heading CMF indicates a CM Fortran feature (CM Fortran is a version of Fortran that was produced by Thinking Machines Corporation). Obsolescent indicates the statement is unchanged from the Fortran 77 definition and has a better replacement in Fortran 90. The final category is @, which indicates a statement that is a PGI extension to HPF/Fortran 90.

Fortran Statements


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 or label of format statement. 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)

See Also

READ, PRINT


ALLOCATABLE 90

The ALLOCATABLE specification statement (attribute) specifies that an array with fixed dimensions is available for a future ALLOCATE statement. An ALLOCATE statement allocates space for the allocatable array.

Syntax

ALLOCATABLE [ :: ] array-name [(deferred-array-spec)]
            [, array-name [(deferred-array-spec)]]...
array-name
is the name of the allocatable array.
deferred-array-spec
is a : character.

Example

	REAL SCORE(:), NAMES(:,:)
REAL, ALLOCATABLE, DIMENSION(:,:,:) :: TEST
ALLOCATABLE SCORE, NAMES
INTEGER, ALLOCATABLE:: REC1(: ,: , :)

See Also

ALLOCATE, DEALLOCATE


ALLOCATE

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

Syntax

ALLOCATE ( allocation-list [ , STAT= var ] )
allocation-list is:
allocate-object [ allocate-shape-spec-list ]
allocate-object is:
variable-name
structure-component
allocate-shape-spec-list is:
[ allocate-lower-bound   :  ] allocate-upper-bound
var
is an integer variable, integer array element or an integer member of a STRUCTURE (that is, an integer scalar memory reference). This variable is assigned a value depending on the success of the ALLOCATE statement.

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.

For an ALLOCATABLE array, the array is allocated with the executable ALLOCATE statement.

Examples

	REAL, ALLOCATABLE :: A(:), B(:)
ALLOCATE (A(10), B(SIZE(A))) REAL A(:,:)
N=3
M=1
ALLOCATE (A(1:11, M:N)) INTEGER FLAG, N
REAL, ALLOCATABLE:: B(:,:)
ALLOCATE (B(N,N),STAT=FLAG)

ARRAY CMF



The ARRAY attribute defines the number of dimensions in an array that may be defined and the number of elements and bounds in each dimension.

Syntax

ARRAY [::] array-name (array-spec) 
[, array-name (array-spec) ] ...
array-name
is the symbolic name of an array.
array-spec
is a valid array specification, either explicit-shape, assumed-shape, deferred-shape, or assumed size (refer to Chapter 4, "Arrays" for details on array specifications).

Description

ARRAY can be used in a subroutine as a synonym for DIMENSION 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 ARRAY is merely to supply a mapping of the argument to the subroutine code, and not to allocate storage.

The typing of the array in an ARRAY statement is defined by the initial letter of the array name in the same way as variable names, 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.

Example

	REAL, ARRAY(3:10):: ARRAY_ONE
INTEGER, ARRAY(3,-2:2):: ARRAY_TWO
This specifies ARRAY_ONE as a vector having eight elements with the lower bound of 3 and the upper bound of 10.

ARRAY_TWO 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.


ASSIGN Obsolescent



The ASSIGN statement assigns a statement label to a variable. Internal procedures can be used in place of the ASSIGN statement. Other cases where the ASSIGN statement was used can be replaced by using character strings (for different format statements that were formally assigned labels by using an integer variable as a format specifier.)

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 statement label in the same program unit as the ASSIGN statement.
  • The label of an executable statement or a FORMAT statement.
A variable must be defined with a statement label when it is referenced:
  • In an assigned GOTO statement.
  • As a format identifier in an input/output statement and while so defined must not be referenced in any other way.
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 77



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=unit
unit is the unit specifier.
ERR=s
s is an executable statement label for the statement used for processing an error condition.
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.

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. Do 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 77



The BLOCK DATA statement introduces a number of statements that initialize data values in COMMON blocks. No executable statements are allowed in a BLOCK DATA segment.

Syntax

BLOCK DATA [name]
   [specification]
END [BLOCK DATA [name]]
name
is a symbol identifying the name of the block data and must be unique among all global names (COMMON block names, program name, module names). If missing, the block data 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 90



The CALL statement transfers control to a subroutine.

Syntax

CALL subroutine [([ actual-arg-list]...])]
subroutine
is the name of the subroutine.
actual-arg-list
has the form:
[ keyword = ]
subroutine-argument
keyword
is a dummy argument name in the subroutine interface.
subroutine-argument
is an actual argument.

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 (&).

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

CASE 90



The CASE statement begins a case-statement-block portion of a SELECT CASE construct.

Syntax

[case-name:]SELECT CASE (case-expr)
[ CASE selector [name]
    block] ... 
[ CASE DEFAULT [case-name]
     block
END SELECT [case-name]

Example

SELECT CASE (FLAG)
CASE ( 1, 2, 3 )
TYPE=1
CASE ( 4:6 )
TYPE=2
CASE DEFAULT
TYPE=0
END SELECT

Type

Executable

See Also

SELECT CASE


CHARACTER 90



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

The syntax for CHARACTER has two forms, the standard Fortran form and the PGI extended form. This section describes both syntax forms.

	CHARACTER [character-selector] [, attribute-list  ::] entity-list
character-selector
the character selector specifies the length of the character string. This has one of several forms:
	([LEN=] type-param-value)
	* character-length [,]
Character-selector also permits a KIND specification. Refer to the Fortran 90 handbook for more syntax details.
attribute-list
is the list of attributes for the character variable.
entity-list
is the list of defined entities.

PGI Syntax Extension @


CHARACTER [*len][,] name [dimension] [*len] [/clist/], ...	

len
is a constant or *. A * is only valid if the corresponding name is a dummy argument.
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

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 
	CHARACTER (LEN=10):: NAME
A is 4 and B is 6 characters long and C is 1 character long. NAME is 10 characters long.

CLOSE 77



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

Syntax

CLOSE ([UNIT=] u  [,ERR= errs ] [,DISP[OSE]= sta]
[,IOSTAT=ios] [,STATUS= sta] )
u
is the external unit specifier where u is an integer.
errs
is an error specifier in 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.
ios
is an integer scalar; 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. A value of -1 indicates an end-of-file condition with no error. A value of -2 indicates an end-of-record condition with no error when using non-advancing I/O.
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' (the quotes are required). 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 program unit. 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 90



The COMMON statement defines global blocks of storage that are either sequential or non sequential. Each common block is identified by the symbolic name defined in the COMMON block.

Syntax

	COMMON /[name ] /nlist  [, /name/nlist]...
name
is the name of each common block and is declared between the /.../ delimiters for a named common and with no name for a blank common.
nlist
is a list of variable names where arrays may be defined in DIMENSION statements or formally declared by their inclusion in the COMMON block.

Description

The name of the COMMON block need not be supplied; without a name, the common is a BLANK COMMON. In this case the compiler uses a default name. There can be several COMMON block statements of the same name in a program segment; these are effectively treated as one statement, with variables 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 program share the same storage area when combined into one executable program and they are defined using the SEQUENCE attribute. In HPF, a common block is non-sequential by default, unless there is an explicit SEQUENCE directive that specifies the array as sequential. Note this may require that older Fortran 77 programs assuming sequence association in COMMON statements have SEQUENCE statements for COMMON variables.

Example

	DIMENSION R(10)
COMMON /HOST/ A, R, Q(3), U
This declares a common block called HOST 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, with a different shape for its elements would require that the array be declared using the SEQUENCE attribute..

		SUBROUTINE DEMO
!HPF$ SEQUENCE HOST
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.

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.

Blank COMMON is always saved.

Blank COMMON may be data initialized.

See Also

The SEQUENCE directive.


COMPLEX 90



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

The syntax for COMPLEX has two forms, the standard Fortran form and the PGI extended form. This section describes both syntax forms.

COMPLEX [ ( [ KIND =] kind-value ) ] [, attribute-list ::] entity-list
COMPLEX permits a KIND specification. Refer to the Fortran 90 handbook for more syntax details.
attribute-list
is the list of attributes for the character variable.
entity-list
is the list of defined entities.

PGI Syntax Extension @

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.

Example

	COMPLEX CURRENT
COMPLEX DIMENSION(8):: CONV1, FLUX1

CONTAINS 90



The CONTAINS statement precedes a subprogram, a function or subroutine, that is defined inside a main program, external subprogram, or module subprogram (internal subprogram). The CONTAINS statement is a flag indicating the presence of a subroutine or function definition. An internal subprogram defines a scope for the internal subprogram's labels and names. Scoping is defined by use and host scoping rules within scoping units. Scoping units have the following precedence for names:

  • A derived-type definition.
  • A procedure interface body.
  • A program unit or a subprogram, excluding contained subprograms.

Syntax

SUBROUTINE X
INTEGER H, I
.
.
.
CONTAINS
SUBROUTINE Y
INTEGER I
I = I + H .
.
END SUBROUTINE Y
END SUBROUTINE X

Type

Non-executable

See Also

MODULE

CONTINUE 77



The 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 ...

CYCLE 90



The CYCLE statement interrupts a DO construct execution and continues with the next iteration of the loop.

Syntax

CYCLE [do-construct-name]

Example

	DO
IF (A(I).EQ.0) CYCLE
B=100/A(I)
IF (B.EQ.5) EXIT
END DO

See Also

EXIT, DO


DATA 77



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 90



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

Syntax

DEALLOCATE ( allocate-object-list [ , STAT= var ] )
Where:
allocate-object-list
is a variable name or a structure component.
var
var the status indicator, is an integer variable, integer array element or an integer member of a structure.

Description

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

	REAL, ALLOCATABLE :: X(:,:)
ALLOCATE (X(10,2)) X=0
DEALLOCATE (X)

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 90



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

Syntax

DIMENSION [::] array-name (array-spec) 
[, array-name (array-spec) ] ...
array-name
is the symbolic name of an array.
array-spec
is a valid array specification, either explicit-shape, assumed-shape, deferred-shape, or assumed size (refer to Chapter 4, "Arrays" for details on array specifications).

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.

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.

Examples

	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
This example sets up an array B with 21 character elements each having a length of four characters. Note that the character 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

The syntax for DOUBLE COMPLEX has two forms, a standard Fortran 90 entity based form, and the PGI extended form. This section describes both syntax forms.

DOUBLE COMPLEX [, attribute-list ::] entity-list
attribute-list
is the list of attributes for the double complex variable.
entity-list
is the list of defined entities.

PGI Syntax Extension

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.

Examples

	DOUBLE COMPLEX CURRENT, NEXT

DOUBLE PRECISION 90



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

The syntax for DOUBLE PRECISION has two forms, a standard Fortran 90 entity based form, and the PGI extended form. This section describes both syntax forms.

DOUBLE PRECISION [, attribute-list ::] entity-list
attribute-list
is the list of attributes for the double precision variable.
entity-list
is the list of defined entities.

PGI Syntax Extension

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.

Example

	DOUBLE PRECISION PLONG

DO (Iterative) 90



The DO statement introduces an iterative loop and specifies the loop control index and parameters. There are two forms of DO statement, block and non-block (Fortran 77 style). There are two forms of block do statements, DO iterative and DO WHILE . Refer to the description of DO WHILE for more details on this form of DO statement.

Syntax DO BLOCK

[do-construct-name : ] DO [label ] [loop-control]
[execution-part-construct]
[label] END DO
loop-control
is increment index expression of the form:
[index = e1 e2 [, e3]]label
labels the last executable statement in the loop (this must not be a transfer of control).
index
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.

Syntax DO NON-BLOCK

DO label [,] index = e1, e2 [, e3]
label
labels the last executable statement in the loop (this must not be a transfer of control).
index
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

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.

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.

Examples

	DO 100 J = -10,10
DO 100 I = -5,5
100 SUM = SUM + ARRAY (I,J) DO
A(I)=A(I)+1
IF (A(I).EQ.4) EXIT
END DO DO I=1,N
A(I)=A(I)+1
END DO

DO WHILE 90



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 continues to be true when tested at the beginning of each iteration. If expression 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..

Example

	DO WHILE (K == 0)
	   SUM = SUM + X
	END DO

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 90



The END statement terminates a segment of a Fortran program. There are several varieties of the END statement. Each is described below.

END Syntax

END

Description

The END statement has the same effect as a RETURN statement in a SUBROUTINE or FUNCTION, or the effect of a STOP statement in a PROGRAM program unit. END may be the last statement in a compilation or it may be followed by a new program unit.

END FILE Syntax

END FILE u
END FILE ([UNIT=]u, [,IOSTAT =ios]  [,ERR=errs]  )
u
is the external unit specifier where u is an integer.
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.

Description

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.

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.

For example:

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


ENTRY 77



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 argument 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 program unit 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 program unit 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:

  • BYTE, INTEGER*2, INTEGER*4, LOGICAL*1, LOGICAL*2, LOGICAL*4, REAL*4, REAL*8, COMPLEX*8
  • COMPLEX*16
  • CHARACTER
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 77



The EQUIVALENCE statement allows two or more named regions of data memory to share the same start address. Arrays that are subject to the EQUIVALENCE statement in HPF are treated as sequential and any attempt at non-replicated data distribution or mapping is ignored for such arrays.

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.

EXIT 90



The EXIT statement interrupts a DO construct execution and continues with the next statement after the loop.

Syntax

EXIT [do-construct-name]

Example

	DO
IF (A(I).EQ.0) CYCLE
B=100/A(I)
IF (B.EQ.5) EXIT
END DO

See Also

CYCLE, DO


EXTERNAL 77



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 program unit. When an external or dummy procedure name is used as an actual argument in a program unit it must appear in an EXTERNAL statement in that program unit.

Description

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


EXTRINSIC HPF



The EXTRINSIC statement identifies a symbolic name as an external or dummy procedure that is written in some language other than HPF.

Syntax

EXTRINSIC ( extrinsic-kind-keyword ) procedure name
extrinsic-kind-keyword
is the name of an extrinsic interface supported. The currently supported value is F77_LOCAL.
procedure name
is either a subroutine-statement or a function-statement defining a name for an external and extrinsic procedure.

Description

The EXTRINSIC procedure can then be used as an actual argument once it is defined. The call to an EXTRINSIC procedure should be semantically equivalent to the execution of an HPF procedure in that on return from the procedure, all processors are still available, and all data and templates will have the same distribution and alignment as when the procedure was called.

See Also

For a complete description of the pghpf extrinsic facility, along with examples, refer to Chapter 8 "Using Modules and Extrinsics", in the pghpf User's Guide.


FORALL HPF



The FORALL statement and the FORALL construct provide a parallel mechanism to assign values to the elements of an array. The FORALL statement is interpreted essentially as a series of single statement FORALL's.

Syntax

FORALL (forall-triplet-spec-list [, scalar-mask-expr] ) forall-assignment
or
FORALL (forall-triplet-spec-list [, scalar-mask-expr] ) 
forall-body
[forall-body ]...
END FORALL
where forall-body is one of:
forall-assignment
where-statement
where-construct
forall-statement
forall-construct

Description

The FORALL statement is computed in four stages:

First, compute the valid set of index values. Second compute the active set of index values, taking into consideration the scalar-mask-expr. If no scalar-mask-expr is present, the valid set is the same as the active set of index values. Third, for each index value, the right-hand-side of the body of the FORALL is computed. Finally, the right-hand-side is assigned to the left-hand-side, for each index value.

Examples

	FORALL (I = 1:3) A(I) = B(I)
	FORALL(I = 1:L, A(I) == 0.0) A(I) = R(I)

	FORALL (I = 1:3) 
		A(I) = D(I)
		B(I) = C(I) * 2
	END FORALL
	FORALL (I = 1:5)
		WHERE (A(I,:) /= 0.0)
			A(I,:) = A(I-1,:) + A(I+1,:)
		ELSEWHERE
			B(I,:) = A(6-I,:)
		END WHERE
	END FORALL



FORMAT 77



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:
  • Repeatable editor commands which may or may not be preceded by an integer constant which defines the number of repeats.
  • Nonrepeatable editor commands.
  • A format specification list optionally preceded by an integer constant which defines the number of repeats.
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 Chapter 6, Input and Output Formatting, for more details on using the FORMAT statement.

Examples

	WRITE (6,90) NPAGE
90 FORMAT('1PAGE NUMBER ',I2,16X,'SALES REPORT, Cont.')
produces:
     PAGE NUMBER 10                 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 90



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

Syntax

[function-prefix] FUNCTION name [*n] ([argument [,argument]...])
.
.
.
END [ FUNCTION [function-name]]
function-prefix
is one of:
[type-spec] RECURSIVE
[RECURSIVE ] type-spec
where type-spec is a valid type specification.
name
is the name of the function and must be unique amongst all the program unit 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 apply only to the function, except for subroutine or function references and the names of COMMON blocks. The function 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 function, unless the RESULT keyword is used. The value of this variable, on exit from the function, is the result of the function. The function 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 and the RECURSIVE prefix is included in the function definition.

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

See Also

PURE, RECURSIVE, RESULT


GOTO (Assigned) Obsolescent



The assigned GOTO statement transfers control so that the statement identified by the statement label is executed next. Internal procedures can be used in place of the ASSIGN statement used with an assigned GO TO.

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 program unit. 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) 77



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) 77



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 program unit containing the GOTO statement and must be unique within that program unit.

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) Obsolescent



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) 90



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 ELSE IF block.

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.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

IMPLICIT 77



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 90



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). INCLUDEEither 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.

The include file is searched for in the following directories:

1. Each -I directory specified on the command-line.

2. The directory containing the file that contains the INCLUDE statement
(the current working directory.)

3. The standard include area.

Example

	INCLUDE  '/mypath/list  /list'
This line includes a file named /mypath/list and expands it in the listing file, if a listing file is used.

INQUIRE 90



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)
In addition list may contain one of each of the following specifiers in any order, following the unit number if the optional UNIT specifier keyword is not supplied.

ACCESS= acc
acc returns a character expression specifying the access method for the file as either DIRECT or SEQUENTIAL.
ACTION= acc
acc is a character expression specifying the access types for the connection. Either READ, WRITE, or READWRITE.
BLANK= blnk
blnk is a character expression which returns the value NULL or ZERO or UNDEFINED.
DELIM= del_char

del_char is a character expression which returns the value APOSTROPHE, QUOTE or NONE or UNDEFINED. These values specify the character delimiter for list-directed or namelist formatted data transfer statements.
DIRECT= dir_char

dir_char a character reference which returns 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 returns the value of a statement label of an executable statement within the same program. If an error condition occurs execution continues with the statement specified by errs.
EXIST= value
value a logical variable or logical array element which becomes .TRUE. if there is a file/unit with the name or .FALSE. otherwise.
FILE= fin
fin is a character expression whose value is the file name expression, the name of the file connected to the specified unit.
FORM= fm
fm is a character expression specifying whether the file is being connected for FORMATTED or UNFORMATTED input/output.
FORMATTED= fmt

fmt a character 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 input/output status specifier where ios is an integer reference: if this is included in list, ios is defined as 0 if no error condition occurred and a positive integer when there is an error condition.
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 (open) and .FALSE. if the file is not connected (.FALSE.).
PAD= pad_char
pad_char is a character expression specifying whether to use blank padding. Values are YES or NO, yes specifies blank padding is used, no requires that input records contain all requested data.
POSITION= pos_char

pos_char is a character expression specifying the file position. Values are ASIS or REWIND or APPEND. For a connected file, on OPEN ASIS leaves the position in the current position, REWIND rewinds the file and APPEND places the current position at the end of the file, immediately before the end-of-file record.
READ= rl
rl a character reference which takes the value YES if UNFORMATTED is one of the allowed access methods for file, NO if not, UNKNOWN if it is not known if UNFORMATTED is included.
READWRITE= rl

rla 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.
RECL= rl
rl is an integer expression defining the record length in a file connected for direct access. When sequential input/output is specified this is the maximum record length.
SEQUENTIAL= seq

seq 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.
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.
WRITE= rl
rl a character scalar memory reference which takes the value YES, NO, or UNKNOWN. Indicates that WRITE is allowed, not allowed, or indeterminate for the specified file.

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 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 90



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

The syntax for INTEGER has two forms, a standard Fortran 90 attributed form, and the PGI extended form. This section describes both syntax forms.

INTEGER [([ KIND = kind-value ) ][, attribute-list ::] entity-list
INTEGER permits a KIND specification. Refer to the Fortran 90 handbook for more syntax details.
attribute-list
is the list of attributes for the character variable.
entity-list
is the list of defined entities.

PGI Syntax Extension

INTEGER [*n] [,] 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.

Example

	INTEGER TIME, SECOND, STORE  (5,5)

INTENT 90



The INTENT specification statement (attribute) specifies intended use of a dummy argument. This statement (attribute) may not be used in a main program's specification statement.

Syntax

INTENT (intent-spec) [ :: ] dummy-arg-list
intent-spec
is one of:
		IN
		OUT
		INOUT
dummy-arg-list
is the list of dummy arguments with the specified intent.

Description

With intent specified as IN, the subprogram argument must not be redefined by the subprogram.

With intent specified as OUT, the subprogram should use the argument to pass information to the calling program.

With intent specified as INOUT, the subprogram may use the value passed through the argument, but should also redefine the argument to pass information to the calling program.

See Also

OPTIONAL

Example

	SUBROUTINE IN_OUT(R1,I1)
REAL, INTENT (IN)::R1
INTEGER, INTENT(OUT)::I1
I1=R1
END SUBROUTINE IN_OUT

INTERFACE 90



The INTERFACE statement block makes an implicit procedure an explicit procedure where the dummy parameters and procedure type are known to the calling module. This statement is also used to overload a procedure name.

Syntax

	INTERFACE [generic-spec]
   [interface-body]...
   [MODULE PROCEDURE procedure-name-list]...
	END INTERFACE

where a generic-spec is either:
	generic-name
	OPERATOR (defined operator)
	ASSIGNMENT (=)

and the interface body specified the interface for a function or a subroutine:

	function-statement
		[specification-part]
	END FUNCTION [function name]

	subroutine-statement
		[specification-part]
	END FUNCTION [subroutine name]

See Also

END INTERFACE

Example

INTERFACE
SUBROUTINE IN_OUT(R1,I1)
REAL, INTENT (IN)::R1
INTEGER, INTENT(OUT)::I1
END SUBROUTINE IN_OUT
END INTEFACE

INTRINSIC 90



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:


* type conversions:

INT, IFIX, IDINT, FLOAT, SNGL, REAL, DBLE, CMPLX, ICHAR, CHAR


* lexical relationships:

LGE, LGT, LLE, LLT

* values:

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 program unit it must appear in an INTRINSIC statement in that program unit. 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 program unit and cannot be used in both an EXTERNAL and INTRINSIC statement in a program unit.

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 90



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

The syntax for LOGICAL has two forms, a standard Fortran 90 attributed form, and the PGI extended form. This section describes both syntax forms.

LOGICAL [ ( [ KIND = kind-value ) ] [, attribute-list ::] entity-list
LOGICAL permits a KIND specification. Refer to the Fortran 90 handbook for more syntax details.
attribute-list
is the list of attributes for the character variable.
entity-list
is the list of defined entities.

PGI Syntax Extension

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

Logical 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.

Example

	LOGICAL TIME, SECOND, STORE  (5,5)

MODULE 90



The MODULE statement specifies the entry point for a module program unit. A module defines a host environment of scope of the module, and may contain subprograms that are in the same scoping unit.

Syntax

MODULE [name]
	[specification-part]
	[ CONTAINS [module-subprogram-part]]
END [MODULE [ module-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.
specification-part

contains specification statements. See the Fortran 90 Handbook for a complete description of the valid statements.
module-subprogram-part

contains function and subroutine definitions for the module, preceded by a single CONTAINS keyword.

Example

MODULE MYOWN
REAL MEAN, TOTAL
INTEGER, ALLOCATABLE, DIMENSION(:):: A
CONTAINS
RECURSIVE INTEGER FUNCTION X(Y)
.
.
.
END FUNCTION X
END MODULE MYOWN

NAMELIST 90



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 consists of a name, an account, and a value.

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

NULLIFY 90



The NULLIFY statement disassociates a pointer from its target.

Syntax

NULLIFY (pointer-object-list)

Example

	NULLIFY (PTR1)

See Also

ALLOCATE, DEALLOCATE

OPEN 90



The OPEN statement connects an existing file to a unit; creates and connects a file to a unit; creates a file that is preconnected or changes 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, following the unit number if the optional UNIT specifier keyword is not supplied.

ACCESS= acc
acc is a character expression specifying the access method for file connection as either DIRECT or SEQUENTIAL - the default is SEQUENTIAL.
ACTION= acc
acc is a character expression specifying the permitted access types for connection. Either READ, WRITE, UNKNOWN or READWRITE are allowed. the default is UNKNOWN .
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.
DELIM= del_char

del_char is a character expression which takes the value 'APOSTROPHE', 'QUOTE' or 'NONE'. These values specify the character delimiter for list-directed or namelist formatted data transfer statements.
ERR=errs
errs an error specifier; takes the form of a statement label of an executable statement within the 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 expression, the name of a file to be connected to the specified unit.
FORM=fm
fm is a character expression specifying whether the file is being connected for 'FORMATTED' or 'UNFORMATTED' input/output.
IOSTAT= ios
ios is an integer scalar; 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. A value of -1 indicates an end-of-file condition with no error. A value of -2 indicates an end-of-record condition with no error when using non-advancing I/O.
PAD= pad_char
pad_char is a character expression specifying whether to use blank padding. Values are YES or NO, yes specifies that blank padding is used and no requires that input records contain all requested data.
POSITION= pos_char

pos_char is a character expression specifying the file position. Values are ASIS or REWIND or APPEND. For a connected file, on OPEN ASIS leaves the position in the current position, REWIND rewinds the file and APPEND places the current position at the end of the file, immediately before the end-of-file record.
RECL= rl
rl is an integer expression defining the record length in a file connected for direct access. When sequential input/output is specified this is the maximum record length.
STATUS= sta
sta is a character expression whose value can be: NEW, OLD, SCRATCH or UNKNOWN or REPLACE. 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.

The unit specified must exist and once connected by an OPEN statement can be referenced in any program unit 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',
+ BLANK='NULL', ACCESS='DIRECT', RECL=98,
+ FORM='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.

OPTIONAL 90



The OPTIONAL specification statement (attribute) specifies dummy arguments that may be omitted or that are optional.

Syntax

OPTIONAL [::] dummy-arg-list

Examples

	OPTIONAL :: VAR4, VAR5

	OPTIONAL VAR6, VAR7

	INTEGER, OPTIONAL:: VAR8, VAR9

See Also

INTENT


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.

Table 3.1 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 checking

CHECK=[NO]UNDERFLOW
None

CHECK=NONE
Disable array bounds checking

NOCHECK
Disable array bounds checking

[NO]EXTEND_SOURCE
(Disable) Enable the -Mextend option

[NO]G_FLOATING
None

[NO]REENTRANT
(Enable) Disable optimizations that may result in code that is not reentrant.



The following restrictions apply to the OPTIONS statement:

  • The OPTIONS statement must be the first statement in a program unit; it must precede the PROGRAM, SUBROUTINE, FUNCTION, and BLOCKDATA statements.
  • The options listed in the OPTIONS statement override values from the driver command-line for the program unit (subprogram) immediately following the OPTIONS statement.
  • Any abbreviated version of an option that is long enough to identify the option uniquely is a legal abbreviation for the option
  • Case is not significant, unless the -Mupcase is present on the command line. If it is, each option must be in lower case.

PARAMETER 77



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 )

PAUSE Obsolescent



The PAUSE statement stops the program's execution. The PAUSE statement is obsolescent because a WRITE statement may send a message to any device, and a READ statement may be used to wait for a message from the same device.

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 90



The POINTER specification statement (attribute) declares a scalar variable to be a pointer variable (of type INTEGER), and another variable to be its target pointer-based variable. The target may be a scalar or an array of any type.

Syntax

POINTER [::] object-name [ (deferred-shape-spec-list) ]
        [, object-name [ ( deferred-shape-spec-list ) ]]

Example

	REAL, DIMENSION(:,:), POINTER:: X


PRINT 77



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.


PRIVATE 90



The PRIVATE statement specifies entities defined in a module are not accessible outside of the module. This statement is only valid in a module. The default specification for a module is PUBLIC.

Syntax

PRIVATE [:: [ access-id-list ]]

Description

Example

MODULE FORMULA
PRIVATE
PUBLIC :: VARA
.
.
.
END MODULE

Type

Non-executable

See Also

PUBLIC, MODULE


PROGRAM 77



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

Syntax

PROGRAM [name]
.
.
.
END [ PROGRAM [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.

The END PROGRAM statement terminates a main program unit that begins with the optional PROGRAM statement. The program name found in the END PROGRAM must match that in the PROGRAM statement.

Example

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

PUBLIC 90



The PUBLIC statement specifies entities defined in a module are accessible outside of the module. This statement is only valid in a module. The default specification for a module is PUBLIC.

Syntax

PUBLIC [ :: [ access-id-list ]]

Example

		
MODULE FORMULA
PRIVATE
PUBLIC :: VARA
.
.
.
END MODULE

Type

Non-executable

See Also

PRIVATE, MODULE


PURE HPF



The PURE attribute indicates whether a function or subroutine has side effects. This indicates if a subroutine or function can be used in a FORALL statement or construct or within an INDEPENDENT DO loop.

Syntax

	PURE [type-specification] FUNCTION
or

	type-specification PURE FUNCTION

or

PURE SUBROUTINE

Type

Non-executable

See Also

FUNCTION, SUBROUTINE


READ 90



The READ statement is the data transfer input statement.

Syntax

    READ  ([unit=] u, format-identifier [,control-information) [iolist]
    READ   format-identifier [,iolist]
        READ   ([unit=] u, [NML=] namelist-group  [,control-information])
where the UNIT= is optional and the external unit specifier u is an integer.

In addition control-information is an optional control specification which can be any of the following: may contain one of each of the following specifiers in any order, following the unit number if the optional UNIT specifier keyword is not supplied.

FMT= format
format a label of a format statement or a variable containing a format string.
NML= namelist
namelist is a namelist group
ADVANCE= spec

spec is a character expression specifying the access method for file connection as either YES or NO.
END=s
s is an executable statement label for the statement used for processing an end of file condition.
EOR=s
s is an executable statement label for the statement used for processing an end of record condition.
ERR=s
s is an executable statement label for the statement used for processing an error condition.
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.
SIZE=n
n is the number of characters read.
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 90



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

The syntax for REAL has two forms, a standard Fortran 90 attributed form, and the PGI extended form. This section describes both syntax forms.

REAL [ ( [ KIND = kind-value ) ] [, attribute-list ::] entity-list
REAL permits a KIND specification. Refer to the Fortran 90 handbook for more syntax details.
attribute-list
is the list of attributes for the character variable.
entity-list
is the list of defined entities.

PGI Syntax Extension


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.


RECURSIVE 90



The RECURSIVE statement indicates whether a function or subroutine may call itself recursively.

Syntax

	RECURSIVE [type-specification] FUNCTION
or

	type-specification RECURSIVE FUNCTION

or

	RECURSIVE SUBROUTINE

Type

Non-executable

See Also

FUNCTION, SUBROUTINE


RETURN 77



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

Syntax

RETURN

RETURN alternate Statement Obsolescent

The alternate RETURN statement is obsolescent for HPF and Fortran 90. Use the CASE statement where possible in new code. 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 expression is greater than or equal to 1 and less than or equal to the number 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 77



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:
UNIT=unit
unit is the unit specifier.
ERR=s
s is an executable statement label for the statement used for processing an error condition. If an error condition occurs execution continues with the statement specified by s.
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.

Examples

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

SAVE 77



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 program unit 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 variables 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:

  • Entities specified by a SAVE statement
  • Entities in blank common or named common
  • Entities initially defined which have not been changed in any way

Example

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

SELECT CASE 90



The SELECT CASE statement begins a CASE construct.

Syntax

[case-name:]SELECT CASE (case-expr)
[ CASE selector [name]
    block] ... 
[ CASE DEFAULT [case-name]
     block
END SELECT [case-name]

Example

SELECT CASE (FLAG)
CASE ( 1, 2, 3 )
TYPE=1
CASE ( 4:6 )
TYPE=2
CASE DEFAULT
TYPE=0
END SELECT

SEQUENCE 90



The SEQUENCE statement is a derived type qualifier that specifies the ordering of the storage associated with the derived type. This statement specifies storage for use with COMMON and EQUIVALENCE statements (the preferred method for derived type data sharing is using MODULES).

Note, there is also an HPF SEQUENCE directive that specifies whether an array, common block, or equivalence is sequential or non-sequential. Refer to Chapter 4, HPF Directives for more information.

Syntax

TYPE 
   [SEQUENCE]
   type-specification...
END TYPE

Example

	TYPE RECORD
SEQUENCE
CHARACTER NAME(25)
INTEGER CUST_NUM
REAL COST
END TYPE

STOP 77



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

Syntax

	STOP [character-expression | digits ]

SUBROUTINE 77



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

Syntax

[RECURSIVE] SUBROUTINE name &
   [(argument[,argument...])] &
	[specification-part]
	[execution-part]
	[internal-subspart]
END [SUBROUTINE [name]]
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.
specification-part

is the specification of data types for the subroutine.
execution-part
contains the subprogram's executable statements.
internal-subs-part

contains subprogram's defined within the subroutine.

Description

A SUBROUTINE must be terminated by an END statement. The statements and names in the subprogram 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 if the -Mrecursive option is used on the command-line and the RECURSIVE prefix is included in the function definition.

Example

	SUBROUTINE DAXTIM (A, X, Y, N, M, ITER,  FP, TOH)
	INTEGER*4    N, M, ITER
REAL*8 A, X(N,M), Y(N,M), FP, TOH . . . END SUBROUTINE DAXTIM

See Also

PURE, RECURSIVE


TARGET 90



The TARGET specification statement (attribute) specifies that a data type may be the object of a pointer variable - that is pointed to by a pointer variable. Likewise, types that do not have the TARGET attribute cannot be the target of a pointer variable.

Syntax

TARGET [ :: ] object-name [(array-spec)]
            [, object-name [(array-spec)]]...

See Also

ALLOCATABLE, POINTER


TYPE 90



The TYPE statement begins a derived type data specification or declares variables of a specified user-defined type.

Syntax Type Declaration

TYPE (type-name) [ , attribute-list :: ] entity-list

Syntax Derived Type Definition


TYPE [[ access-spec ] :: ] type-name
 [ private-sequence-statement ] ...
component-definition-statement
 [ component-definition-statement ]...
END TYPE [type-name]  

USE 90



The USE statement gives a program unit access to the public entities or to the named entities in the specified module.

Syntax

USE module-name [, rename-list ]
USE module-name, ONLY: [ only-list ]

Description

A module-name file has an associated compiled .mod file that is included when the module is used. The .mod file is searched for in the following directories:

1. Each -I directory specified on the command-line.

2. The directory containing the file that contains the USE statement
(the current working directory.)

3. The standard include area.

Examples

USE MOD1

USE MOD2, TEMP => VAR

USE MOD3, ONLY: RESULTS, SCORES => VAR2

Type

Non-executable

See Also

MODULE


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

WHERE 90



The WHERE statement and the WHERE END WHERE construct permit masked assignments to the elements of an array (or to a scalar, zero dimensional array).

Syntax WHERE Statement

WHERE (logical-array-expr) array-variable = array-expr

Syntax WHERE Construct

WHERE (logical-array-expr)
   array-assignments
[ELSE WHERE
   array-assignments ]
END WHERE

Description

This construct allows for conditional assignment to an array based on the result of a logical array expression. The logical array expression and the array assignments must involve arrays of the same shape.

Examples

	INTEGER    SCORE(30)
CHARACTER GRADE(30)
WHERE ( SCORE > 60 ) GRADE = 'P'
WHERE ( SCORE > 60 )
GRADE = 'P'
ELSE WHERE
GRADE = 'F'
END WHERE

WRITE 90



The WRITE statement is a data transfer output statement.

Syntax

    WRITE  ([unit=] u, [,control-information) [iolist]
    WRITE  ([unit=] u, [NML=] namelist-group  [,control-information])
where the UNIT= is optional and the external unit specifier u is an integer. This may also be a * indicating list-directed output.

In addition to the unit specification, control-information are optional control specifications, and may be any of those listed in the following (there are some limits on the allowed specifications depending on the type of output, for example, non-advancing, direct and sequential):

ADVANCE=spec
spec is a character expression specifying the access method for the write. YES indicates advancing formatted sequential data transfer. NO indicates nonadvancing formatted sequential data transfer.
ERR=s
s is an executable statement label for the statement used for processing an error condition.
[FMT=]format
format a label of a format statement or a variable containing a format string.
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.
[NML=] namelist

namelist is a namelist group
REC=rn
rn is a record number to read and must be a positive integer. This is only used for direct access files.
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.


<< << " border=0> >> > " border=0> Title Contents Index Home Help

Powered by Plone This site conforms to the following standards: