INQUIRE (Fortran 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 (Fortran 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 (Fortran 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 (Fortran 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 (Fortran 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:

INT, IFIX, IDINT, FLOAT, SNGL, REAL, DBLE, CMPLX, ICHAR, CHAR
LGE, LGT, LLE, LLT
MAX, MAX0, AMAX1, DMAX1, AMAX0, MAX1, MIN, MIN0, AMIN1, DMIN1, AMIN0, MIN1
When a specific name of an intrinsic function is used as an actual argument in a 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 (Fortran 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 (Fortran 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 (Fortran 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


Note

The pghpf 2.0 compiler ignores distribution directives applied to namelist arrays. Support for legal distributions of namelist groups will be added in a future release of pghpf.




NULLIFY (Fortran 90)

The NULLIFY statement disassociates a pointer from its target.

Syntax

NULLIFY (pointer-object-list)

Example

	NULLIFY PTR1

See Also

ALLOCATE, DEALLOCATE


OPEN (Fortran 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 (Fortran 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:

PARAMETER (Fortran 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 (Fortran 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.

Note

The POINTER statement is not implemented in version 2.0 of pghpf.

Syntax

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

Example

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



PRINT (Fortran 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 (Fortran 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 (Fortran 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 (Fortran 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-excutable

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.

Syntax

	PURE [type-specification] FUNCTION
or

	type-specification PURE FUNCTION

or

PURE SUBROUTINE

Type

Non-executable

See Also

FUNCTION, SUBROUTINE



READ (Fortran 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 (Fortran 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 (Fortran 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 (Fortran 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 (Fortran 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 (Fortran 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:

Example

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


SELECT CASE (Fortran 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 (Fortran 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 specifes whether an array, common block, or equvalence 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 (Fortran 77)

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

Syntax

	STOP [character-expression | digits ]


SUBROUTINE (Fortran 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]
	[exectuion-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 (Fortran 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.

Note

The TARGET statement is not implemented in version 2.0 of pghpf.

Syntax

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

See Also

ALLOCATABLE, POINTER



TYPE (Fortran 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 (Fortran 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 ]

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 (Fortran 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 (Fortran 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.')