BLOCK DATA
CHARACTER variable list
COMMON variable list
COMMON/block name/variable list
DATA variable list
DIMENSION variable list
DOUBLE PRECISION variable list
ENTRYentry name (argument list)
EQUIVALENCE (equivalence list)
EXTERNAL subprogram list
*FORMAT (format specification list)
FUNCTION function name (agrument list)
IMPLICIT declaration list
INTEGER variable list
INTRINSIC subprogram list
LOGICAL variable list
PARAMETER (constant assignment list)
PROGRAM program name
REAL varoab;e ;ost
SAVE variable list
SUBROUTINE subroutine name (argument list)
Variable name = expression
ASSIGN statement label TO integer variable
BACKSPACE (UNIT = integer expression)
CALL subroutine name (argument list)
CLOSE (UNIT = integer expression)
*CONTINUE
DO statement label index = initial, limit, increment
END
ENDFILE (UNIT = integer expression)
* These statements must have a statement number.
GO TO statement label
GO TO integer variable, (statement label, ..., statement label)
GO TO (statement label, ..., statement label), integer expression
IF (condition) executable statements
IF (arithmetic expression) statement label, statement label, statement label
IF (condition) THEN
executable statements
END IF
IF (condition) THEN
executable statements
ELSE
executable statements
END IF
IF (condition) THEN
executable statements
ELSE IF (condition) THEN
executable statements
END IF
INQUIRE (FILE=character expression, inquiry
specifier list)
INQUIRE (UNIT=integer expression, inquiry
specifier list)
OPEN (UNIT=integer expression, FILE=character
expression, STATUS=character expression)
PRINT*, expression list
PRINT k, expression list
READ*, variable list
READ (unit number, format number) variable list
READ k, variable list
READ (unit number, format number, REC=integer
expression) variable list
RETURN integer expression
REWIND (UNIT=integer expression)
STOP
WRITE unit number, format number) expression list
WRITE (unit number, format number, REC=integer
expression) expression list
In the following table of intrinsic functions, the names of the arguments specify their type as indicated below:
Argument | Type | |
---|---|---|
X | __ | real |
CHX | __ | character |
DX | __ | double precision |
CX | __ | complex, a + bi |
LX | __ | logical |
IX | __ | integer |
GX | __ | generic |
Function type, the second column of the table of intrinsic functions, specifies the type of value returned by the function.
Generic function names are printed in color. Any type argument that is applicable can be used with generic functions, and the function value returned will be the same type as the input arguments, except for type conversion functions such as REAL and INT.
Function Name | Function Type | Definition |
---|---|---|
SORT(X) | Real | square root of X |
DSORT(DX) | Double precision | square root of DX |
CSORT(CX) | Complex | square root of X |
ABS(X) | Real | absolute value of X |
IABS(IX) | Integer | absolute value of IX |
DABS(DX) | Double precision | absolute value of DX |
CABS(CS) | Complex | absolute value of CS |
EXP(X) | Real | e |
DEXP(DX) | Double precision | e |
CEXP(CX) | Complex | e |
LOG(GX) | Same as GX | logeGX |
ALOG(X) | Real | logeX |
DLOG(DX) | Double precision | logeDX |
CLOG(CX) | Complex | logeCS |
LOG10(GX) | Same as GX | log10GX |
ALOG10(X) | Real | log10X |
DLOG10(DX) | Double precision | log10DX |
REAL(GX) | Real | Convert GX to real value |
FLOAT(IX) | Real | Convert IX to real value |
SNGL(DX) | Real | Convert DX to single precision |
ANINT(X) | Real | Round to nearest whole number |
DNINT(DX) | Double precision | Round to nearest whole number |
NINT(X) | Integer | Round to nearest integer |
IDNINT(DX) | Integer | Round to nearest integer |
AINT(X) | Real | Truncate X to whole number |
DINT(DX) | Double precision | Truncate DX to whole number |
INT(GX) | Integer | Truncate GX to an integer |
IFIX(X) | Integer | Truncate X to an integer |
IDINT(DX) | Integer | Truncate DX to an integer |
SIGN(X, Y) | Real | Transfer sign of Y to (X) |
ISIGN(IX, IY) | Integer | Transfer sign of IY to (IX) |
DSIGN(DX, DY) | Double precision | Transfer sign of DY to (DX) |
MOD(IX, IY) | Integer | Remainder from IX/IY |
AMOD(X, Y) | Real | Remainder from X/Y |
DMOD(DX, DY) | Double precision | Remainder from DX/DY |
DIM(X, Y) | Real | X - (minimum of X and Y) |
IDIM(IX, Y) | Integer | IX - (minimum of IX and IY) |
DDIM(DX, DY) | Double precision | DX - (minimum of DX and DY) |
MAX(GX, GY, ...) | Same as Gx, GY, ... | Maximum of (GX,GY,...) |
MAXO(IX,IY,...) | Integer | Maximum of (IX,IY,...) |
AMAX1(X,Y,...) | Real | Maximum of (X,Y,...) |
DMAX1(DX,DY,...) | Double precision | Maximum of (DX,DY,...) |
AMAXO(IX,IY,...) | Real | Maximum of (IX,IY,...) |
MAX1(X,Y,...) | Integer | Maximum of (X,Y,...) |
MIN(GX,GY,... | Same as GX,GY,... | Minimum of (GX,GY,...) |
Integer | Minimum of (IX,IY,...) | |
ADReal | Minimum of (X,Y,...) | |
DMIN1(DX,DY,...) | Double precision | Minimum of (DX,DY,...) |
AMINO(IX,IY,...) | Real | Minimum of (IX,IY,...) |
MIN1(X,Y,...) | Integer | Minimum of (X,Y,...) |
SIN(X) | Real | Sine of X, assumes radians |
DSIN(DX) | Double precision | Sine of DX, assumes radians |
CSIN(CX) | Complex | Sine of CX |
COS(X) | Real | Cosine of X, assumes radians |
DCOS(DX) | Double precision | Cosine of DX, assumes radians |
CCOS(CX) | Complex | Cosine of CS |
TAN(X) | Real | Tangent of X, assumes radians |
DTAN(DX) | Double precision | Tangent of DX, assumes radians |
ASIN(X) | Real | Arcsine of X |
DASIN(DX) | Double precision | Arcsine of DX |
ACOS(X) | Real | Arccosine of X |
DACPS(DX) | Double precision | Arccosine of DX |
ATAN(X) | Real | Arctangent of X |
DATAN(DX) | Double precision | Arctangent of DX |
ATAN2(X,Y) | Real | Arctangent of X/Y |
DATAN(DX) | Double precision | Arctangent of DX/DY |
SINH(X) | Real | Hyperbolic sine of X |
Double precision | Hyperbolic sine of DX | |
COSH(X) | Real | Hyperbolic cosine of X |
DCOSH(DX) | Double precision | Hyperbolic cosine of DX |
TANH(X) | Real | Hyperbolic tangent of X |
DTANH(DX) | Double precision | Hyperbolic tangent of DX |
DPROD(X,Y) | Double precision | Product of X and Y |
DBLE(X) | Double precision | Convert X to double precision |
CMPLX(X) | Complex | X + Oi |
CMPLX(X,Y) | Complex | X + Yi |
AIMAG(CX) | Real | Imaginary part of CX |
REAL(CX) | Real | Real part of CX |
CONJG(CX) | Complex | Conjugate of CX, a - bi |
LEN(CHX) | Complex | Length of character string CHX |
INDEX(CHX,CHY) | Integer | Position of substring CHY in string CHX |
ICHAR(CHX) | Integer | Position of the character CHX in the collating sequence |
LGT(CHX,CHY) | Logical | Value of (CHX is lexically greater than CHY) |
LLE(CHX,CHY) | Logical | Value of (CHX is lexically less than or equal to CHY) |
LLT(CHX,CHY) | Logical | Value of (CHX is lexically less than CHY) |
LGE(CHX,CHY) | Logical | Value of (CHX is lexically greater than or equal to CHY) |
A format is used with formatted PRINT, WRITE, and READ statements and provides information that directs the conversion between internal data representations and external data representations in a file. A format specifier is designated by:
Formally, method 1 is referred to as list-directed I/O, and methods 2 and 3 are referred to as user-formatted I/O, usually shortened to the term formatted I/O. The edit descriptors that can be used with user-formatted I/O are listed in Table B-1.
Edit descriptors are interpreted from left to right in a format specification, and input and output records are edited from left to right. If there are insufficient edit descriptors in a format specification for an input or output list, format control is transferred to the first open parentheses in the specification.
Descriptor | Description |
---|---|
rlw | Edits integer data |
rFw.d | Edits both real and double precision data in decimal format |
rEw.d | Edits real data in exponential format |
rDw.d | Edits double precision data in exponential format |
rGw.d | Edits both real and double precision data in exponential format |
Lw | Edits logical data |
rAw | Edits character data |
'a..a' | Specifies a character constant |
Tc | Tabs to position c |
TLn | Tabs backward n positions |
| |
TRn | Tabs forward n positions |
nX | Skips over n positions (same as TRn) |
/ | Causes the current record to be written or the next record to be read |
SS | Suppresses printing of plus sign |
BN | Ignores blank spaces in a field |
BZ | Considers blank spaces in a field to be zeros |
kP | Multiplies each number by 10 |
Notes: | r is an optional unsigned nonzero positive integer used as repeat count. |
w is an unsigned nonzero positive integer that specifies the data field width. | |
d is an unsigned positive integer that specifies the number of places to the right of the decimal point. | |
a is any character. | |
c is an unsigned positive nonzero integer. | |
n is an unsigned positive nonzero integer. | |
k is an unsigned positive nonzero integer. |
The table below presents the symbols, precedence, descriptions, and associativity of FORTRAN's operators. Operators toward the top of the table have a higher precedence than those toward the bottom. Operators within each category have the same precedence and associativity.
Arithmetical operations that are undefined mathematically are also undefined in FOTRAN77. Thus, it is illegal to divide by zero, raise a zero-valued operand to a zeroth or negative power, or raise a negative operand to a real or double precision power.
Operator | Description | Associativity |
---|---|---|
( ) | Parentheses | Inner to outer |
** | Exponentiation | Right to left |
* | Multiplication | Left to right |
/ | Division | Left to right |
+ | Addition | left to right |
- | Subtraction | Left to right |
// | Concatenation | Left to right |
.GT. | Relational | Left to right |
.GE. | Relational | Left to right |
.LT. | Relational | Left to right |
.EQ. | Relational | Left to right |
.NE. | Relational | Left to right |
.NOT. | Logical negation | Left to right |
.AND. | Logical conjunction | Left to right |
.OR. | Logical inclusion | Left to right |
.EQV. | Logical equivalence | Left to right |
.NEQV. | Logical nonequivalence | Left to right |
Note: Where no optional blank is indicated between two adjacent keywords, the blank is mandatory.
StatementPROGRAM
program-nameMODULE
module-nameEND[ ][MODULE [
module-name]]USE
module-name [,rename-list]USE
module-name, ONLY:
[only-list]PRIVATE[[::]
access-id-list]PUBLIC[[::]
access-id-list]EXTERNAL
external-name-listINTRINSIC
intrinsic-name-list[RECURSIVE] SUBROUTINE
subroutine-name FUNCTION
function-name([dummy-argument-list])
RESULT
(result-name)]RECURSIVE
] or RECURSIVE
[type]ENTRY
entry-name [(]dummy-argument-list]) [RESULT
(result-name)]]INTENT
(inout) [::] dummy-argument-name-listIN, OUT,
or IN[ ]OUT
OPTIONAL
[::] dummy-argument-name-listSAVE
[ [::] saved-entity-list]CONTAINS
INTERFACE
[generic-spec]OPERATOR
(defined-operator), or ASSIGNMENT(=)
END[ ]INTERFACE
MODULE PROCEDURE
procedure-name-listINTEGER
[([KIND=
]kind-value)],REAL
[([KIND=
kind-value)], LOGICAL
[([KIND=
]kind-value)],COMPLEX
[([KIND=
]kind-value)],CHARACTER
[actual-parameter-list], DOUBLE
[ ]PRECISION
, or TYPE
(type-name)PARAMETER, PUBLIC, PRIVATE, POINTER, TARGET, ALLOCATABLE,
DIMENSION
(extent-list), INTENT
(inout) EXTERNAL, INTRINSIC, OPTIONAL
or SAVE
IMPLICIT NONE
IMPLICIT
type(letter-spec-list) [,type(letter-spec-list)]...TYPE
[, access::] type-namePUBLIC
or PRIVATE
POINTER
or DIMENSION
(extent-list)END
[ ] TYPE
[type-name]SEQUENCE
DATA
Object-list/value-list/[[,] object-list/value-list/]...BLOCK
[ ]DATA
[block-data-name]END
[[ ]BLOCK
[ ]DATA
[block-data-name]]PARAMETER
(named-constant-definition-list)NAMELIST
/namelist-group-name/ variable-name-list[[,]/namelist-group-name/DIMENSION
array-name(array-spec) [, (array-name(array-spec)]...ALLOCATABLE
[::] array-name[(array-spec)] [,array-name[(array-spec)] ]...POINTER
[::] object-name[(array-spec)] [,object-name[(array-spec)] ]...TARGET
[::] object-name[(array-spec)] [,object-name[(array-spec)] ]...EQUIVALENCE
(object, object-list) [, (object, object-list)]...COMMON
[/]cname[[,]/[cname]/ vlist]...IF
(scalar-logical-expr) action-stmtWHERE
(logical-array-expr) array-variable = array-exprCALL
subroutine-name [([actual-argument-list])]RETURN
END
[ ][unit[unit-name]]PROGRAM, SUBROUTINE,
or FUNCTION
. ALLOCATE
(allocation-list [, STAT
=stat])DEALLOCATE
(allocate-object-list [, STAT
=stat])NULLIFY
(pointer-object-list)DO
[label] [,] do-variable = scalar-integer-expr, scalar-integer-expr [,scalar-integer-expr]DO
[label] [,] WHILE
(scalar-logical-expr)CYCLE
[do-name]EXIT
[do-name]CONTINUE
END
[ ]DO
[do-name]IF
(scalar-logical-expr) THEN
ELSE
[[ ]IF
(scalar-logical-expr) THEN
[ ]if-name]END
[ ]IF
[if-name]SELECT
[ ]CASE
(scalar-expr)CASE
(case-value-list) [select-name]CASE DEFAULT
[select-name]END
[ ]SELECT
[select-name]GO
[ ]TO
labelSTOP
[access-code]WHERE
(logical-away-expr)ELSEWHERE
END
[ ]WHERE
GO
[ ]TO
(sl1, sl2, sl3, ...) [,] integerREAD
(control-list) [input-list]READ
format[,input-list]WRITE
(control-list) [output-list]PRINT
format [,output-list]REWIND
external-file-unitREWIND
(position-list)END
[ ]FILE
external-file-unitEND
[ ]FILE
position-listBACKSPACE
external-file-unitOPEN
(connect-list)CLOSE
(close-list)INQUIRE
(inquire-list)INQUIRE
(IOLENGTH
= length) olistFORMAT
([format-list]) (this statement is actually non-executable).Name | Description |
---|---|
ABS (A) | Absolute value. |
ACHAR(I) | Character in position I of ASCII collating sequence. |
ACOS (X) | Arc cosine (inverse cosine) function. |
ADJUSTL (STRING) | Adjust left, removing leading blanks and inserting trailing blanks. |
ADJUSTR (STRING) | Adjust right, removing trailing blanks and inserting leading blanks. |
AIMAG (Z) | Imaginary part of complex number. |
AINT (A[,KIND]) | Truncate to a whole number |
ALL (MASK [,DIM]) | True if all elements are true |
ALLOCATED (ARRAY) | True if the array is allocated. |
ANINT (A,[,KIND]) | Nearest whole number. |
ANY (MASK [,DIM]) | True if any element is true. |
ASIN (X) | Arcsine (inverse sine) function. |
ASSOCIATED (POINTER [,TARGET]) |
True if pointer is associated with target |
ATAN (X) | Arctangent (inverse tangent) function |
ATAN2 (Y,X) | Argument of complex number (X, Y). |
BIT_SIZE (1) | Maximum number of bits that may be held in an integer. |
BTEST (I, POS) | True if bit POS of integer I has value 1. |
CEILING (A) | Least integer greater than or equal to its argument. |
CHAR (I [,KIND]) | Character in position I of the processor collating sequence. |
CMPLX (X[,Y] [,KIND]) | Convert to COMPLEX type. |
CONJG (Z) | Conjugate of a complex number. |
COS (X) | Cosine function. |
COSH (X) | |
COUNT (MASK [,DIM]) | Number of true elements. |
CSHIFT (ARRAY, SHIFT, [DIM]) | Perform circular shift. |
CALL DATE_AND_TIME (DATE] [,TIME] {,ZONE] [,VALUES]) | Real-time clock reading date and time. |
DBLE (A) | Convert to double precision real. |
DIGITS (X) | Number of significant digits in the model for X. |
DIM (X,Y) | Max(X-Y,0). |
DOT_PRODUCT (VECTOR_A, VECTOR_B) | Dotproduct. |
DPROD (X, Y) | Double precision real product of two default real scalars. |
EOSHIFT (ARRAY, SHIFT [,BOUNDARY] [,DIM]) | Perform end-off shift. |
EPSILON (X) | Number that is almost negligible compared with one in the model for numbers like X. |
EXP (X) | Exponential function. |
EXPONENT (X) | Exponent part of the model for X. |
FLOOR (A) | Greatest integer less than or equal to its argument. |
FRACTION (X) | Fractional part of the model for X. |
HUGE (X) | Largest number in the model for numbers like X. |
LACHAR (C) | Position of character C in ASCII collating sequence. |
LAND (I, J) | Logical AND on the bits. |
IBCLR (I, POS) | Clear bit POS to zero. |
IBITS (I, POS, LEN) | Extract a sequence of bits |
IBSET (I, POS) | Set bit POS to one. |
OCJAR (C) | Position of character C in the processor collating sequence. |
IEOR (I, J) | Exclusive OR on the bits |
INDEX (STRING, SUBSTRING [BACK]) | Starting position of SUBSTRING within STRING. |
INT (A [,KIND]) | Convert to integer type. |
IOR (I, J) | Inclusive OR on the bits. |
ISHFT (I, SHIFT) | Logical shift on the bits. |
ISHFTC (I, SHIFT [,SIZE]) | Logical circular shift on a set of bits on the right. |
KIND (X) | Kind type parameter value. |
LBOUND (ARRAY [,DIM]) | Array lower bounds. |
LEN (STRING) | Character length. |
LEN_TRIM (STRING) | Length of STRING without trailing blanks. |
LGE (STRING_A, STRING_B) | True if STRING_A equals or follows STRING_B in ASCII collating sequence. |
LGT (STRING_A, STRING_B) | True if STRING_A follows STRING_B in ASCII collating sequence. |
LLE (STRING_A, STRING_B) | True if STRING_A equals or precedes STRING_B in ASCII collating sequence. |
LLT (STRING_A, STRING_B) | True if STRING_A precedes STRING_B in ASCII collating sequence. |
LOG (X) | Natural (base e logarithm function. |
LOGICAL (L,[,KIND]) | Convert between kinds of logicals. |
LOG10 (X) | Common (base 10) logarithm function. |
MATMUL (MATRIX_A, MATRIX_B) | Matrix multiplication. |
MAX (A1,A2[,A3...]) | Maximum value. |
MAXEXPONENT (X) | Maximum exponent in the model for numbers like X. |
MAXLOC (ARRAY [,MASK]) | Location of maximum array element. |
MAXVAL (ARRAY [,DIM] [,MASK]) | Value of maximum array element. |
MERGE (TSOURCE, FSOURCE, MASK) | TSOURCE when MASK is true and FSOURCE otherwise. |
MIN (A1,A2 [,A3,...]) | Minimum value. |
MINEXPONENT (X) | Minimum exponent in the model for numbers like X. |
MINLOC (ARRAY [,MASK]) | Location of minimum array element. |
MINVAL (ARRAY [,DIM] [,MASK]) | Value of minimum array element. |
MOD (A,P) | Remainder modulo P, that is A-INT(A/P)*P. |
MODULO (A,P) | A modulo P. |
CALL MVBITS (FROM, FROMPOS, LEN, TO, POS) | Copy bits. |
NEAREST (X, S) | Nearest different machine number in the direction given by the sign of S. |
NINT (A [,KIND]) | Nearest integer. |
NOT (I) | Logical complement of the bits |
PACK (ARRAY, MASK [VECTOR]) | Pack elements corresponding to true elements of MASK into rank-one result. |
PRECISION (X) | Decimal precision in the model for X. |
PRESENT (A) | True if optional argument is present. |
PRODUCT (ARRAY [,DIM] [,MASK]) | Product of array elements. |
RADIX (X) | Base of the model for numbers like X. |
CALL RANDOM_NUMBER (HARVEST) | Random numbers in range 0 -< x <1. |
CALL RANDOM_SEED ([SIZE][,PUT][,GET]) | Initialize or restart random number generator. |
RANGE (X) | Decimal exponent range in the model for X. |
REAL (A [,KIND]) | Convert to real type. |
REPEAT (STRING, NCOPIES) | Concatenates NCOPIES of STRING. |
RESHAPE (SOURCE, SHAPE [,PAD] [,ORDER]) | Reshape SOURCE to shape SHAPE. |
RESPACING (X) | Reciprocal of the relative spacing of model numbers near X. |
SCALE (X, I) | X x b |
SCAN (STRING, SET [,BACK]) | Index of left-most (right-most if BACK is true) character of STRING that belongs to SET; zero if none belong. |
SELECTED_INT_KIND (R) | Kind of type parameter for specified exponent range. |
SELECTED_REAL_KIND ([P] [,R]) | Kind of type parameter for specified precision and exponent range. |
SET_EXPONENT (X, I) | Model number whose sign and fractional part are those of X and whose exponent part is I. |
SHAPE (SOURCE) | Array (or scalar) shape. |
SIGN (A, B) | Absolute value of A times sign of B. |
SIN (X) | Sine function. |
SINH (X) | Hyperbolic sine function. |
SIZE (ARRAY [,DIM]) | Array size |
SPACINE (X) | Absolute spacing of model numbers near X. |
SPREAD (SOURCE, DIM, NCOPIES) | NCOPIES copies of SOURCE forming an array of rank one greater. |
SQRT (X) | Square root function. |
SUM (ARRAY, [,DIM] [,MASK]) | Sum of array elements. |
CALL SYSTEM_CLOCK ([COUNT] [,COUNT_RATE] [,COUNT_MAX]) | Integer data from real-time clock |
TAN (X) | Tangent function. |
TANH (X) | Hyperbolic tangent function. |
TINY (X) | Smallest positive number in the model for numbers like X. |
TRANSFER (SOURCE, MOLD [,SIZE]) | Same physical representation as SOURCE, but type of MOLD. |
TRANSPOSE (MATRIX) | Matrix transpose. |
TRIM (STRING) | Remove trailing blanks from a single string. |
UBOUND (ARRAY [,DIM]) | Array upper bounds. |
UNPACK (VECTOR, MASK, FIELD) | Unpack elements of VECTOR corresponding to true elements of MASK. |
VERIFY (STRING, SET [,BACK]) | Zero if all characters of STRING belong to SET or index of left-most (right-most if BACK true) that does not. |