FORTRAN 77 Language Reference

Chapter 4 Statements

This chapter describes the statements recognized by Sun FORTRAN 77. Nonstandard features are indicated by the symbol "@". (See Chapter 1 for a discussion of the conforming standards). A table of sample statements appears in Appendix B.

ACCEPT 

The ACCEPT @ statement reads from standard input and requires the following syntax:

ACCEPT f [, iolist]

ACCEPT grname

Parameter 

Description 

f

Format identifier 

iolist

List of variables, substrings, arrays, and records 

grname

Name of the namelist group 

Description

ACCEPT f [,iolist] is equivalent to READ f [,iolist] and is for compatibility with older versions of FORTRAN. An example of list-directed input:


       REAL VECTOR(10) 
       ACCEPT *, NODE, VECTOR 

ASSIGN

The ASSIGN statement assigns a statement label to a variable.

ASSIGN s TO i

Parameter 

Description 

s

Statement label  

i

Integer variable 

Description

The label s is the label of an executable statement or a FORMAT statement.

The statement label must be the label of a statement that is defined in the same program unit as the ASSIGN statement.

The integer variable i, once assigned a statement label, can be reassigned the same statement label, a different label, or an integer. It can not be declared INTEGER*2.

After assigning a statement label to a variable, you can reference it in:

Restrictions

The variable must be assigned a statement label before referencing it as a label in an assigned GO TO statement, or as a format identifier.

While i is assigned a statement label value, do no arithmetic with i.

On 64-bit platforms, the actual value stored in variable i by the ASSIGN statement is not available to the program, except by the assigned GO TO statement, or as a format identifier in an I/O statement. Also, only variables set by an ASSIGN statement can be used in an assigned GO TO or as a format identifier.

Examples

Example 1: Assign the statement number of an executable statement:


       IF(LB.EQ.0) ASSIGN 9 TO K 
       ... 
       GO TO K 
       ... 
9      AKX = 0.0

Example 2: Assign the statement number of a format statement:


       INTEGER PHORMAT 
2      FORMAT ( A80 ) 
       ASSIGN 2 TO PHORMAT 
       ... 
       WRITE ( *, PHORMAT ) 'Assigned a FORMAT statement no.' 

Assignment

The assignment statement assigns a value to a variable, substring, array element, record, or record field.

v = e

Parameter 

Description 

v

Variable, substring, array element, record, or record field  

e

Expression giving the value to be assigned 

Description

The value can be a constant or the result of an expression. The kinds of assignment statements: are arithmetic, logical, character, and record assignments.

Arithmetic Assignment

v is of numeric type and is the name of a variable, array element, or record field.

e is an arithmetic expression, a character constant, or a logical expression. Assigning logicals to numerics is nonstandard, and may not be portable; the resultant data type is, of course, the data type of v. @

Execution of an arithmetic assignment statement causes the evaluation of the expression e, and conversion to the type of v (if types differ), and assignment of v with the resulting value typed according to the following table.

Type of v

Type of e

INTEGER*2, INTEGER*4, or INTEGER*8

REAL

REAL*8

REAL*16 (SPARC only)

DOUBLE PRECISION

COMPLEX*8

COMPLEX*16

COMPLEX*32 (SPARC only)

INT(e)

REAL(e)

REAL*8

QREAL(e) (SPARC only)

DBLE(e)

CMPLX(e)

DCMPLX(e)

QCMPLX(e) (SPARC only)


Note -

Compiling with any of the options -i2, -dbl, -r8, or -xtypemap can alter the default data size of variables and expressions. This is discussed in Chapter 2. See also the Fortran User's Guide for a description of these options.


Example: An assignment statement:


       REAL A, B 
       DOUBLE PRECISION V 
       V = A * B 

The above code is compiled exactly as if it were the following:


       REAL A, B 
       DOUBLE PRECISION V 
       V = DBLE( A * B )

Logical Assignment

v is the name of a variable, array element, or record field of type logical.

e is a logical expression, or an integer between -128 and 127, or a single character constant.

Execution of a logical assignment statement causes evaluation of the logical expression e and assignment of the resulting value to v. If e is a logical expression (rather than an integer between -128 and 127, or a single character constant), then e must have a value of either true or false.

Logical expressions of any size can be assigned to logical variables of any size. The section on the LOGICAL statement provides more details on the size of logical variables.

Character Assignment

The constant can be a Hollerith constant or a string of characters delimited by apostrophes (') or quotes ("). The character string cannot include the control characters Control-A, Control-B, or Control-C; that is, you cannot hold down the Control key and press the A, B, or C keys. If you need those control characters, use the char() function.

If you use quotes to delimit a character constant, then you cannot compile with the -xl option, because, in that case, a quote introduces an octal constant. The characters are transferred to the variables without any conversion of data, and may not be portable.

Character expressions which include the // operator can be assigned only to items of type CHARACTER. Here, the v is the name of a variable, substring, array element, or record field of type CHARACTER; e is a character expression.

Execution of a character assignment statement causes evaluation of the character expression and assignment of the resulting value to v. If the length of e is more than that of v, characters on the right are truncated. If the length of e is less than that of v, blank characters are padded on the right.

Record Assignment

v and e are each a record or record field. @

The e and v must have the same structure. They have the same structure if any of the following occur:

The sections on the RECORD and STRUCTURE statements have more details on the structure of records.

Examples

Example 1: Arithmetic assignment:


       INTEGER I2*2, J2*2, I4*4 
       REAL R1, QP*16 							! (REAL*16 is SPARC only)
       DOUBLE PRECISION DP 
       COMPLEX C8, C16*16, QC*32 	! (COMPLEX*32 is SPARC only)
       J2 = 29002 
       I2 = J2 
       I4 = (I2 * 2) + 1 
       DP = 6.4D9 
       QP = 6.4Q9 
       R1 = DP 
       C8 = R1 
       C8 = ( 3.0, 5.0 ) 
       I2 = C8 
       C16 = C8 
       C32 = C8 

Example 2: Logical assignment:


       LOGICAL B1*1, B2*1
       LOGICAL L3, L4
       L4 = .TRUE.
       B1 = L4
       B2 = B1

Example 3: Hollerith assignment:


       CHARACTER S*4 
       INTEGER I2*2, I4*4 
       REAL R
       S = 4Hwxyz 
       I2 = 2Hyz 
       I4 = 4Hwxyz 
       R = 4Hwxyz

Example 4: Character assignment:


       CHARACTER BELL*1, C2*2, C3*3, C5*5, C6*6 
       REAL Z
       C2 = 'z' 
       C3 = 'uvwxyz' 
       C5 = 'vwxyz' 
       C5(1:2) = 'AB' 
       C6 = C5 // C2 
       BELL = CHAR(7)    Control Character (^G)

The results of the above are

C2

C3

C5

C6

receives 'zD' a trailing blank

receives 'uvw'

receives 'ABxyz'

receives 'ABxyzz' an extra z left over from C5

BELL

receives 07 hex Control-G, a bell

:

Example 5: Record assignment and record field assignment:


       STRUCTURE /PRODUCT/ 
              INTEGER*4 ID 
              CHARACTER*16 NAME 
              CHARACTER*8 MODEL 
              REAL*4 COST 
              REAL*4 PRICE 
       END STRUCTURE 
       RECORD /PRODUCT/ CURRENT, PRIOR, NEXT, LINE(10) 
       ... 
       CURRENT = NEXT                Record to record 
       LINE(1) = CURRENT        Record to array element 
       WRITE ( 9 ) CURRENT   Write whole record 
       NEXT.ID = 82                    Assign a value to a field 

AUTOMATIC

The AUTOMATIC @ statement makes each recursive invocation of the subprogram have its own copy of the specified items. It also makes the specified items become undefined outside the subprogram when the subprogram exits through a RETURN statement.

AUTOMATIC vlist

Parameter 

Description 

vlist

List of variables and arrays  

Description

For automatic variables, there is one copy for each invocation of the procedure. To avoid local variables becoming undefined between invocations, f77 classifies every variable as either static or automatic with all local variables being static by default. For other than the default, you can declare variables as static or automatic in a STATIC @, AUTOMATIC @, or IMPLICIT statement. See also the discussion of the -stackvar option in the Fortran User's Guide.

One usage of AUTOMATIC is to declare all automatic at the start of a function.

Example: Recursive function with implicit automatic:


       INTEGER FUNCTION NFCTRL( I )
       IMPLICIT AUTOMATIC (A-Z)
       ...
       RETURN
       END

Local variables and arrays are static by default, so in general, there is no need to use SAVE. You should use SAVE to ensure portability. Also, SAVE is safer if you leave a subprogram by some way other than a RETURN.

Restrictions

Automatic variables and arrays cannot appear in DATA or SAVE statements.

Arguments and function values cannot appear in DATA, RECORD, STATIC, or SAVE statements because f77 always makes them automatic.

Examples

Example: Some other uses of AUTOMATIC:


       AUTOMATIC A, B, C 
       REAL P, D, Q 
       AUTOMATIC P, D, Q 
       IMPLICIT AUTOMATIC (X-Z) 

Example: Structures are unpredictable if AUTOMATIC:


demo% cat autostru.f
       AUTOMATIC X
       STRUCTURE /ABC/
       INTEGER I
       END STRUCTURE
       RECORD /ABC/ X     X is automatic. It cannot be a structure.
       X.I = 1
       PRINT '(I2)', X.I
       END
demo% f77 -silent autostru.f
demo% a.out
*** TERMINATING a.out
*** Received signal 10 (SIGBUS)
Bus Error (core dumped)
demo%

Restrictions

An AUTOMATIC statement and a type statement cannot be combined to make an AUTOMATIC type statement. For example, AUTOMATIC REAL X does not declare the variable X to be both AUTOMATIC and REAL; it declares the variable REALX to be AUTOMATIC.

BACKSPACE

The BACKSPACE statement positions the specified file to just before the preceding record.

BACKSPACE u

BACKSPACE ([UNIT= ] u [, IOSTAT=ios ] [, ERR=s ])

Parameter 

Description 

u

Unit identifier of the external unit connected to the file  

ios

I/O status specifier, integer variable, or an integer array element 

s

Error specifier: s must be the label of an executable statement in the same program unit in which the BACKSPACE statement occurs. Program control is transferred to the label in case of an error during the execution of the BACKSPACE statement.

Description

BACKSPACE in a terminal file has no effect.

u must be connected for sequential access. Execution of a BACKSPACE statement on a direct-access file is not defined in the FORTRAN 77 Standard, and is unpredictable. We do not recommend using a BACKSPACE statement on a direct-access file or an append access file.

Execution of the BACKSPACE statement modifies the file position, as follows:

Prior to Execution 

After Execution 

Beginning of the file  

Remains unchanged  

Beyond the endfile record  

Before the endfile record  

Beginning of the previous record 

Start of the same record 

Examples

Example 1: Simple backspace


       BACKSPACE 2 
       LUNIT = 2 
       BACKSPACE LUNIT 

:

Example 2: Backspace with error trap:


       INTEGER CODE
       BACKSPACE ( 2, IOSTAT=CODE, ERR=9 ) 
       ... 
9      WRITE (*,*) 'Error during BACKSPACE' 
       STOP 

BLOCK DATA

The BLOCK DATA statement identifies a subprogram that initializes variables and arrays in labeled common blocks.

BLOCK DATA [name]

Parameter 

Description 

name

Symbolic name of the block data subprogram in which the BLOCK DATA statement appears. This parameter is optional. It is a global name.

Description

A block data subprogram can contain as many labeled common blocks and data initializations as desired.

The BLOCK DATA statement must be the first statement in a block data subprogram.

The only other statements that can appear in a block data subprogram are:

Only an entity defined in a labeled common block can be initially defined in a block data subprogram.

If an entity in a labeled common block is initially defined, all entities having storage units in the common block storage sequence must be specified, even if they are not all initially defined.

Restrictions

Only one unnamed block data subprogram can appear in the executable program.

The same labeled common block cannot be specified in more than one block data subprogram in the same executable program.

The optional parameter name must not be the same as the name of an external procedure, main program, common block, or other block data subprogram in the same executable program. The name must not be the same as any local name in the subprogram.

Example


       BLOCK DATA INIT 
       COMMON /RANGE/ X0, X1 
       DATA X0, X1 / 2.0, 6.0 / 
       END 

BYTE

The BYTE @ statement specifies the type to be 1-byte integer. It optionally specifies array dimensions and initializes with values.

BYTE v [/c/]

Parameter 

Description 

v

Name of a symbolic constant, variable, array, array declarator, function, or dummy function  

c

List of constants for the immediately preceding name  

Description

This is a synonym for LOGICAL*1. A BYTE type item can hold the logical values .TRUE., .FALSE., one character, or an integer between -128 and 127.

Example


       BYTE BIT3 /8/, C1/'W'/, M/127/, SWITCH/.FALSE./

CALL

The CALL statement branches to the specified subroutine, executes the subroutine, and returns to the calling program after finishing the subroutine.

CALL sub [([ar[, ar]])]

Parameter 

Description 

sub

Name of the subroutine to be called  

ar

Actual argument to be passed to the subroutine 

Description

Arguments are separated by commas.

The FORTRAN 77 Standard requires that actual arguments in a CALL statement must agree in order, number, and type with the corresponding formal arguments of the referenced subroutine. The compiler checks this only when the -XlistE option is on.

Recursion is allowed. A subprogram can call itself directly, or indirectly by calling another subprogram that in turns calls this subroutine. Such recursion is nonstandard. @

An actual argument, ar, must be one of the following:

The simplest expressions, and most frequently used, include such constructs as:

If a subroutine has no arguments, then a CALL statement that references that subroutine must not have any actual arguments. A pair of empty matching parentheses can follow the subroutine name.

Execution of the CALL statement proceeds as follows:

  1. All expressions (arguments) are evaluated.

  2. All actual arguments are associated with the corresponding formal arguments, and the body of the subroutine is executed.

  3. Normally, the control is transferred back to the statement following the CALL statement upon executing a RETURN statement or an END statement in the subroutine. If an alternate return in the form of RETURN n is executed, then control is transferred to the statement specified by the n alternate return specifier in the CALL statement.


    Note -

    A CALL to a subprogram defined as a FUNCTION rather than as a SUBROUTINE will cause unexpected results and is not recommended. The compiler does not automatically detect such inappropriate CALLs and no warning is issued unless the -Xlist option is specified.


Examples

Example 1: Character string:


       CHARACTER *25 TEXT 
       TEXT = 'Some kind of text string' 
       CALL OOPS ( TEXT )
       END
       SUBROUTINE OOPS ( S )
              CHARACTER S*(*) 
              WRITE (*,*) S 
       END

Example 2: Alternate return:


       CALL RANK ( N, *8, *9 ) 
       WRITE (*,*) 'OK - Normal Return' 
       STOP 
8     WRITE (*,*) 'Minor - 1st alternate return' 
       STOP 
9     WRITE (*,*) 'Major - 2nd alternate return' 
       STOP 
       END 

       SUBROUTINE RANK ( N, *, * ) 
              IF ( N .EQ. 0 ) RETURN 
              IF ( N .EQ. 1 ) RETURN 1 
              RETURN 2 
       END 

Example 3: Another form of alternate return; the & is nonstandard:


       CALL RANK ( N, &8, &9 )

@

Example 4: Array, array element, and variable:


       REAL M(100,100), Q(2,2), Y 
       CALL SBRX ( M, Q(1,2), Y ) 
       ... 
       END 
       SUBROUTINE SBRX ( A, D, E ) 
       REAL A(100,100), D, E 
       ... 
       RETURN 
       END 

In this example, the real array M matches the real array, A, and the real array element Q(1,2) matches the real variable, D.

Example 5: A structured record and field; the record is nonstandard: @


       STRUCTURE /PRODUCT/ 
              INTEGER*4 ID 
              CHARACTER*16 NAME 
              CHARACTER*8 MODEL 
              REAL*4 COST 
              REAL*4 PRICE 
       END STRUCTURE 
       RECORD /PRODUCT/ CURRENT, PRIOR 
       CALL SBRX ( CURRENT, PRIOR.ID ) 
       ... 
       END 
       SUBROUTINE SBRX ( NEW, K ) 
       STRUCTURE /PRODUCT/ 
              INTEGER*4 ID 
              CHARACTER*16 NAME 
              CHARACTER*8 MODEL 
              REAL*4 COST 
              REAL*4 PRICE 
       END STRUCTURE 
       RECORD /PRODUCT/ NEW 
       ... 
       RETURN 
       END 

In the above example, the record NEW matches the record CURRENT, and the integer variable, K, matches the record field, PRIOR.OLD.

CHARACTER

The CHARACTER statement specifies the type of a symbolic constant, variable, array, function, or dummy function to be character.

Optionally, it initializes any of the items with values and specifies array dimensions.

CHARACTER [* len[,]] v [* len /c/]]

Parameter 

Description 

v

Name of a symbolic constant, variable, array, array declarator, function, or dummy function  

len

Length in characters of the symbolic constant, variable, array element, or function  

c

List of constants for the immediately preceding name  

Description

Each character occupies 8 bits of storage, aligned on a character boundary. Character arrays and common blocks containing character variables are packed in an array of character variables. The first character of one element follows the last character of the preceding element, without holes.

The length, len must be greater than 0. If len is omitted, it is assumed equal to 1.

For local and common character variables, symbolic constants, dummy arguments, or function names, len can be an integer constant, or a parenthesized integer constant expression.

For dummy arguments or function names, len can have another form: a parenthesized asterisk, that is, CHARACTER*(*), which denotes that the function name length is defined in referencing the program unit, and the dummy argument has the length of the actual argument.

For symbolic constants, len can also be a parenthesized asterisk, which indicates that the name is defined as having the length of the constant. This is shown in Example 5 in the next section.

The list c of constants can be used only for a variable, array, or array declarator. There can be only one constant for the immediately preceding variable, and one constant for each element of the immediately preceding array.

Examples

Example 1: Character strings and arrays of character strings:


       CHARACTER*17 A, B(3,4), V(9) 
       CHARACTER*(6+3) C 

The above code is exactly equivalent to the following:


       CHARACTER A*17, B(3,4)*17, V(9)*17 
       CHARACTER C*(6+3) 

Both of the above two examples are equivalent to the nonstandard variation: @


       CHARACTER A*17, B*17(3,4), V*17(9)	 nonstandard

There are no null (zero-length) character-string variables. A one-byte character string assigned a null constant has the length zero.

Example 2: No null character-string variables:


       CHARACTER S*1
       S = ''

During execution of the assignment statement, the variable S is precleared to blank, and then zero characters are moved into S, so S contains one blank; because of the declaration, the intrinsic function LEN(S) will return a length of 1. You cannot declare a size of less than 1, so this is the smallest length string variable you can get.

Example 3: Dummy argument character string with constant length:


       SUBROUTINE SWAN( A ) 
       CHARACTER A*32 

Example 4: Dummy argument character string with length the same as corresponding actual argument:


       SUBROUTINE SWAN( A ) 
       CHARACTER A*(*) 
       ... 

Example 5: Symbolic constant with parenthesized asterisk:


       CHARACTER *(*) INODE 
       PARAMETER (INODE = 'Warning: INODE corrupted!')

The intrinsic function LEN(INODE) returns the actual declared length of a character string. This is mainly for use with CHAR*(*) dummy arguments.

Example 6: The LEN intrinsic function:


       CHARACTER A*17
       A = "xyz"
       PRINT *, LEN( A )
        END

The above program displays 17, not 3.

CLOSE

The CLOSE statement disconnects a file from a unit.

CLOSE([UNIT=] u [, STATUS= sta] [, IOSTAT= ios] [, ERR= s])

Parameter 

Description 

u

Unit identifier for an external unit. If UNIT= is not used, then u must be first.

sta

Determines the disposition of the file--sta is a character expression whose value, when trailing blanks are removed, can be KEEP or DELETE. The default value for the status specifier is KEEP. For temporary (scratch) files, sta is forced to DELETE always. For other files besides scratch files, the default sta is KEEP.

ios

I/O status specifier--ios must be an integer variable or an integer array element.

s

Error specifier--s must be the label of an executable statement in the same program containing the CLOSE statement. The program control is transferred to this statement in case an error occurs while executing the CLOSE statement.

Description

The options can be specified in any order.

The DISP= and DISPOSE= options are allowable alternates for STATUS=, with a warning, if the -ansi flag is set.

Execution of CLOSE proceeds as follows:

  1. The specified unit is disconnected.

  2. If sta is DELETE, the file connected to the specified unit is deleted.

  3. If an IOSTAT argument is specified, ios is set to zero if no error was encountered; otherwise, it is set to a positive value.

Comments

All open files are closed with default sta at normal program termination. Regardless of the specified sta, scratch files, when closed, are always deleted.

Execution of a CLOSE statement specifying a unit that does not exist, or a unit that has no file connected to it, has no effect.

Execution of a CLOSE statement specifying a unit zero (standard error) is not allowed, but you can reopen it to some other file.

The unit or file disconnected by the execution of a CLOSE statement can be connected again to the same, or a different, file or unit.


Note -

For tape I/O, use the TOPEN() routines.


Examples

Example 1: Close and keep:


       CLOSE ( 2, STATUS='KEEP') 

Example 2: Close and delete:


       CLOSE ( 2, STATUS='DELETE', IOSTAT=I )

Example 3: Close and keep a scratch file even though the status is SCRATCH:


       OPEN ( 2, STATUS='SCRATCH') 
       ... 
       CLOSE ( 2, STATUS='KEEP', IOSTAT=I ) 

COMMON

The COMMON statement defines a block of main memory storage so that different program units can share the same data without using arguments.

COMMON [/[cb]/] nlist [[,]/[cb]/ nlist]

Parameter 

Description 

cb

Common block name 

nlist

List of variable names, array names, and array declarators 

Description

If the common block name is omitted, then blank common block is assumed.

Any common block name including blank common can appear more than once in COMMON statements in the same program unit. The list nlist following each successive appearance of the same common block name is treated as a continuation of the list for that common block name.

The size of a common block is the sum of the sizes of all the entities in the common block, plus space for alignment.

Within a program, all common blocks in different program units that have the same name must be of the same size. However, blank common blocks within a program are not required to be of the same size.

Restrictions

Formal argument names and function names cannot appear in a COMMON statement.

An EQUIVALENCE statement must not cause the storage sequences of two different common blocks in the same program unit to be associated. See Example 2.

An EQUIVALENCE statement must not cause a common block to be extended on the left-hand side. See Example 4.

Examples

Example 1:


       DIMENSION V(100) 
       COMMON V, M 
       COMMON /LIMITS/I, J 
       ... 

Unlabeled common and labeled common:

In the above example, V and M are in the unlabeled common block; I and J are defined in the named common block, LIMITS.

Example 2: You cannot associate storage of two different common blocks in the same program unit:


       COMMON /X/ A 
       COMMON /Y/ B 
       EQUIVALENCE ( A, B)			        Not allowed

Example 3: An EQUIVALENCE statement can extend a common block on the right-hand side:


       DIMENSION A(5) 
       COMMON /X/ B 
       EQUIVALENCE ( B, A) 

Example 4: An EQUIVALENCE statement must not cause a common block to be extended on the left-hand side:


       COMMON /X/ A 
       REAL B(2) 
       EQUIVALENCE ( A, B(2))			   Not allowed 

COMPLEX

The COMPLEX statement specifies the type of a symbolic constant, variable, array, function, or dummy function to be complex, optionally specifies array dimensions and size, and initializes with values.

COMPLEX [*len[,]] v [*len[/c/]] [, v [*len[/c/]] ...

Parameter 

Description 

v

Name of a symbolic constant, variable, array, array declarator, function, or dummy function  

len

Either 8, 16, or 32, the length in bytes of the symbolic constant, variable, array element, or function (32 is SPARC only)

c

List of constants for the immediately preceding name  

Description

The declarations can be: COMPLEX, COMPLEX*8, COMPLEX*16, or COMPLEX*32. Specifying the size is nonstandard. @

COMPLEX

For a declaration such as COMPLEX W, the variable W is usually two REAL*4 elements contiguous in memory, interpreted as a complex number.

If you do not specify the size, a default size is used.

The default size for a declaration such as COMPLEX W can be altered by compiling with any of the options -dbl, -r8, or -xtypemap. See the discussion in Chapter 2 for details.

COMPLEX*8 @

For a declaration such as COMPLEX*8 W, the variable W is always two REAL*4 elements contiguous in memory, interpreted as a complex number.

COMPLEX*16 @

For a declaration such as COMPLEX*16 W, W is always two REAL*8 elements contiguous in memory, interpreted as a double-width complex number.

COMPLEX*32 @

(SPARC only) For a declaration such as COMPLEX*32 W, the variable W is always two REAL*16 elements contiguous in memory, interpreted as a quadruple-width complex number.

Comments

There is a double-complex version of each complex built-in function. Generally, the specific function names begin with Z or CD instead of C, except for the two functions DIMAG and DREAL, which return a real value.

There are specific complex functions for quad precision (SPARC only). In general, where there is a specific REAL a corresponding COMPLEX with a C prefix, and a corresponding COMPLEX DOUBLE with a CD prefix, there is also a quad-precision COMPLEX function with a CQ prefix. Examples are: SIN(), CSIN(), CDSIN(), CQSIN().

Examples

Example 1: Complex variables. These statements are equivalent.


       COMPLEX U, V
       COMPLEX*8 U, V
       COMPLEX U*8, V*8 

Example 2: Initialize complex variables:


       COMPLEX U/(1, 9.0)/,V/(4.0, 5)/ 

A complex constant is a pair of numbers, either integers or reals.

Example 3: Double complex, with initialization:


       COMPLEX U*16 / (1.0D0, 9 ) /, V*16 / (4.0, 5.0D0) / 
       COMPLEX*16 X / (1.0D0, 9.0) /, Y / (4.0D0, 5 ) /

A double-complex constant is a pair of numbers, and at least one number of the pair must be double precision.

Example 4: Quadruple complex, with initialization (SPARC only):


       COMPLEX U*32 / (1.0Q0, 9 ) /, V*32 / (4.0, 5.0Q0) / 
       COMPLEX*32 X / (1.0Q0, 9.0) /, Y / (4.0Q0, 5 ) / 

A quadruple complex constant is a pair of numbers, and at least one number of the pair must be quadruple precision.

Example 5: Complex arrays, all of which are nonstandard (SPARC only):


       COMPLEX R*16(5), S(5)*16 
       COMPLEX U*32(5), V(5)*32 
       COMPLEX X*8(5), Y(5)*8

CONTINUE

The CONTINUE statement is a "do-nothing" statement.

[label] CONTINUE

Parameter 

Description 

label

Executable statement number 

Description

The CONTINUE statement is often used as a place to hang a statement label, usually it is the end of a DO loop.

The CONTINUE statement is used primarily as a convenient point for placing a statement label, particularly as the terminal statement in a DO loop. Execution of a CONTINUE statement has no effect.

If the CONTINUE statement is used as the terminal statement of a DO loop, the next statement executed depends on the DO loop exit condition.

Example


       DIMENSION U(100) 
       S = 0.0 
       DO 1 J = 1, 100 
              S = S + U(J) 
              IF ( S .GE. 1000000 ) GO TO 2 
1      CONTINUE 
       STOP 
2      CONTINUE 
       . . .

DATA

The DATA statement initializes variables, substrings, arrays, and array elements.

DATA nlist / clist / [[,] nlist / clist /] ...

Parameter 

Description 

nlist

List of variables, arrays, array elements, substrings, and implied DO lists separated by commas

clist

List of the form: c [, c ]

c

One of the forms: c or r*c, and c is a constant or the symbolic name of a constant.

r

Nonzero, unsigned integer constant or the symbolic name of such constant 

Description

All initially defined items are defined with the specified values when an executable program begins running.

r*c is equivalent to r successive occurrences of the constant c.

A DATA statement is a nonexecutable statement, and must appear after all specification statements, but it can be interspersed with statement functions and executable statements, although this is non-standard@.


Note -

Initializing a local variable in a DATA statement after an executable reference to that variable is flagged as an error when compiling with the -stackvar option. See the Sun Fortran User's Guide.


Taking into account the repeat factor, the number of constants in clist must be equal to the number of items in the nlist. The appearance of an array in nlist is equivalent to specifying a list of all elements in that array. Array elements can be indexed by constant subscripts only.

Automatic variables or arrays cannot appear on a DATA statement.

Normal type conversion takes place for each noncharacter member of the clist.

Character Constants in the DATA Statement

If the length of a character item in nlist is greater than the length of the corresponding constant in clist, it is padded with blank characters on the right.

If the length of a character item in nlist is less than that of the corresponding constant in clist, the additional rightmost characters are ignored.

If the constant in clist is of integer type and the item of nlist is of character type, they must conform to the following rules:

If the constant of clist is a character constant or a Hollerith constant, and the item of nlist is of type INTEGER, then the number of characters that can be assigned is 2 or 4 for INTEGER*2 and INTEGER*4 respectively. If the character constant or the Hollerith constant has fewer characters than the capacity of the item, the constant is extended on the right with spaces. If the character or the Hollerith constant contains more characters than can be stored, the constant is truncated on the right.

Implied DO Lists

An nlist can specify an implied DO list for initialization of array elements.

The form of an implied DO list is:

(dlist, iv=m1, m2 [, m3])

Parameter 

Description 

dlist

List of array element names and implied DO lists

iv

Integer variable, called the implied DO variable

m1

Integer constant expression specifying the initial value of iv

m2

Integer constant expression specifying the limit value of iv

m3

Integer constant expression specifying the increment value of iv. If m3 is omitted, then a default value of 1 is assumed.

The range of an implied DO loop is dlist. The iteration count for the implied DO is computed from m1, m2, and m3, and it must be positive.

Implied DO lists may also appear within the variables lists on I/O statements PRINT, READ, and WRITE.

Variables

Variables can also be initialized in type statements. This is an extension of the FORTRAN 77 Standard. Examples are given under each of the individual type statements and under the general type statement. @

Examples

Example 1: Character, integer, and real scalars. Real arrays:


       CHARACTER TTL*16 
       REAL VEC(5), PAIR(2) 
       DATA TTL /'Arbitrary Titles'/, 
&            M /9/, N /0/, 
&            PAIR(1) /9.0/, 
&            VEC /3*9.0, 0.1, 0.9/ 
       ... 

Example 2: Arrays--implied DO:


       REAL R(3,2), S(4,4) 
       DATA ( S(I,I), I=1,4)/4*1.0/, 
&           ( R(I,J), J=1,3), I=1,2)/6*1.0/ 
       ... 

Example 3: Mixing an integer and a character:


       CHARACTER CR*1 
       INTEGER I*2, N*4 
       DATA I /'00'/,N/4Hs12t/,CR/13/
       ... 

DECODE/ENCODE

ENCODE writes to a character variable, array, or array element.@ DECODE reads from a character variable, array, or array element. Data is edited according to the format identifier.

Similar functionality can be accomplished, using internal files with formatted sequential WRITE statements and READ statements. ENCODE and DECODE are not in the FORTRAN 77 Standard, and are provided for compatibility with older versions of FORTRAN.

ENCODE (size, f, buf [, IOSTAT=ios] [, ERR=s]) [iolist]

DECODE (size, f, buf [, IOSTAT=ios] [, ERR=s]) [iolist]

Parameter 

Description 

size

Number of characters to be translated, an integer expression 

f

Format identifier, either the label of a FORMAT statement, or a character expression specifying the format string, or an asterisk.

buf

Variable, array, or array element 

ios

I/O status specifier, ios must be an integer variable or an integer array element.

s

The error specifier (statement label) s must be the label of executable statement in the same program unit in which the ENCODE and DECODE statement occurs.

iolist

List of input/output items.  

Description

The entities in the I/O list can be: variables, substrings, arrays, array elements, record fields. A simple unsubscripted array name specifies all of the elements of the array in memory storage order, with the leftmost subscript increasing more rapidly.

Execution proceeds as follows:

  1. The ENCODE statement translates the list items to character form according to the format identifier, and stores the characters in buf. A WRITE operation on internal files does the same.

  2. The DECODE statement translates the character data in buf to internal (binary) form according to the format identifier, and stores the items in the list. A READ statement does the same.

  3. If buf is an array, its elements are processed in the order of subscript progression, with the leftmost subscript increasing more rapidly.

  4. The number of characters that an ENCODE or a DECODE statement can process depends on the data type of buf. For example, an INTEGER*2 array can contain two characters per element, so that the maximum number of characters is twice the number of elements in that array. A character variable or character array element can contain characters equal in number to its length. A character array can contain characters equal in number to the length of each element multiplied by the number of elements.

  5. The interaction between the format identifier and the I/O list is the same as for a formatted I/O statement.

Example

A program using DECODE/ENCODE:


       CHARACTER S*6 / '987654' /, T*6 
       INTEGER V(3)*4 
       DECODE( 6, '(3I2)', S ) V 
       WRITE( *, '(3I3)') V 
       ENCODE( 6, '(3I2)', T ) V(3), V(2), V(1) 
       PRINT *, T 
       END

The above program has this output:


98 76 54 
547698

The DECODE reads the characters of S as 3 integers, and stores them into V(1), V(2), and V(3).

The ENCODE statement writes the values V(3), V(2), and V(1) into T as characters; T then contains '547698'.

DIMENSION

The DIMENSION statement specifies the number of dimensions for an array, including the number of elements in each dimension.

Optionally, the DIMENSION statement initializes items with values.

DIMENSION a(d) [, a(d)] ...

Parameter 

Description 

a

Name of an array  

d

Specifies the dimensions of the array. It is a list of 1 to 7 declarators separated by commas. 

Description

This section contains descriptions for the dimension declarator and the arrays.

Dimension Declarator

The lower and upper limits of each dimension are designated by a dimension declarator. The form of a dimension declarator is:

[ dd1 :] dd2

dd1 and dd2 are dimension bound expressions specifying the lower- and upper- bound values. They can be arithmetic expressions of type integer or real. They can be formed using constants, symbolic constants, formal arguments, or variables defined in the COMMON statement. Array references and references to user-defined functions cannot be used in the dimension bound expression. dd2 can also be an asterisk. If dd1 is not specified, a value of one is assumed. The value of dd1 must be less than or equal to dd2.

Nonconstant dimension-bound expressions can be used in a subprogram to define adjustable arrays, but not in a main program.

Noninteger dimension bound expressions are converted to integers before use. Any fractional part is truncated.

Adjustable Array

If the dimension declarator is an arithmetic expression that contains formal arguments or variables defined in the COMMON statement, then the array is called an adjustable array. In such cases, the dimension is equal to the initial value of the argument upon entry into the subprogram.

Assumed-Size Array

The array is called an assumed-size array when the dimension declarator contains an asterisk. In such cases, the upper bound of that dimension is not stipulated. An asterisk can only appear for formal arrays and as the upper bound of the last dimension in an array declarator.

Examples

Example 1: Arrays in a main program:


       DIMENSION M(4,4), V(1000) 
       ... 
       END 

In the above example, M is specified as an array of dimensions 4 ¥4 and V is specified as an array of dimension 1000.

Example 2: An adjustable array in a subroutine:


       SUBROUTINE INV( M, N ) 
       DIMENSION M( N, N ) 
       ... 
       END 

In the above example, the formal arguments are an array, M, and a variable N. M is specified to be a square array of dimensions N¥ N.

Example 3: Lower and upper bounds:


       DIMENSION HELIO (-3:3, 4, 3:9) 
       ... 
       END 

In the above example, HELIO is a 3-dimensional array. The first element is HELIO(-3,1,3) and the last element is HELIO(3,4,9).

Example 4: Dummy array with lower and upper bounds:


       SUBROUTINE ENHANCE( A, NLO, NHI ) 
       DIMENSION A(NLO : NHI) 
       ... 
       END 

Example 5: Noninteger bounds


       PARAMETER ( LO = 1, HI = 9.3 ) 
       DIMENSION A(HI, HI*3 + LO ) 
       ... 
       END

:

In the above example, A is an array of dimension 9¥28.

Example 6: Adjustable array with noninteger bounds:


       SUBROUTINE ENHANCE( A, X, Y ) 
       DIMENSION A(X : Y) 
       ... 
       END

Example 7: Assumed-size arrays:


       SUBROUTINE RUN(A,B,N)
       DIMENSION A(*), B(N,*)
       ...

DO

The DO statement repeatedly executes a set of statements.

DO s [,] loop-control

or

DO loop-control @

where s is a statement number. The form of loop-control is

variable = e1, e2 [, e3]

Parameter 

Description 

variable

Variable of type integer, real, or double precision. 

e1, e2, e3

Expressions of type integer, real or double precision, specifying initial, limit, and increment values respectively.  

Description

The DO statement contains the following constructs.

Labeled DO Loop

A labeled DO loop consists of the following:

Terminal Statement

The statement identified by s is called the terminal statement. It must follow the DO statement in the sequence of statements within the same program unit as the DO statement.

The terminal statement should not be one of the following statements:

If the terminal statement is a logical IF statement, it can contain any executable statement, except:

DO Loop Range

The range of a DO loop consists of all of the executable statements that appear following the DO statement, up to and including the terminal statement.

If a DO statement appears within the range of another DO loop, its range must be entirely contained within the range of the outer DO loop. More than one labeled DO loop can have the same terminal statement.

If a DO statement appears within an IF, ELSE IF, or ELSE block, the range of the associated DO loop must be contained entirely within that block.

If a block IF statement appears within the range of a DO loop, the corresponding END IF statement must also appear within the range of that DO loop.

Block DO Loop @

A block DO loop consists of:

This loop is nonstandard.

Execution proceeds as follows:

  1. The expressions e1, e2, and e3 are evaluated. If e3 is not present, its value is assumed to be one.

  2. The DO variable is initialized with the value of e1.

  3. The iteration count is established as the value of the expression:

    MAX (INT ((e2 - e1 + e3)/),e3 0)

    The iteration count is zero if either of the following is true:

    • e1 > e2 and e3 > zero.

    • e1 < e2 and e3 < zero.

      If the -onetrip compile time option is specified, then the iteration count is never less than one.

  4. The iteration count is tested, and, if it is greater than zero, the range of the DO loop is executed.

Terminal Statement Processing

After the terminal statement of a DO loop is executed, the following steps are performed:

  1. The value of the DO variable, if any, is incremented by the value of e3 that was computed when the DO statement was executed.

  2. The iteration count is decreased by one.

  3. The iteration count is tested, and if it is greater than zero, the statements in the range of the DO loop are executed again.

Restrictions

The DO variable must not be modified in any way within the range of the DO loop.

Control must not jump into the range of a DO loop from outside its range.

Comments

In some cases, the DO variable can overflow as a result of an increment that is performed prior to testing it against the final value. When this happens, your program has an error, and neither the compiler nor the runtime system detects it. In this situation, though the DO variable wraps around, the loop can terminate properly.

If there is a jump into the range of a DO loop from outside its range, a warning is issued, but execution continues anyway.

When the jump is from outside to the terminal statement that is CONTINUE, and this statement is the terminal statement of several nested DO loops, then the most inner DO loop is always executed.

Examples

Example 1: Nested DO loops:


       N = 0 
       DO 210 I = 1, 10 
       J = I 
       DO 200 K = 5, 1 
              L = K
              N = N + 1 
200 CONTINUE 
210 CONTINUE 
       WRITE(*,*)'I =',I, ', J =',J, ', K =',K, 
&              ', N =',N, ', L =',L
       END
demo% f77 -silent DoNest1.f
"DoNest1.f", line 4: Warning: DO range never executed
demo% a.out
I =  11, J =  10, K =  5, N =  0, L =  0
demo%

The inner loop is not executed, and at the WRITE, L is undefined. Here L is shown as 0, but that is implementation-dependent; do not rely on it.

Example 2: The program DoNest2.f (DO variable always defined):


       INTEGER COUNT, OUTER 
       COUNT = 0 
              DO OUTER = 1, 5 
                     NOUT = OUTER 
                     DO INNER = 1, 3 
                            NIN = INNER 
                            COUNT = COUNT+1 
                     END DO 
              END DO 
       WRITE(*,*) OUTER, NOUT, INNER, NIN, COUNT 
       END 

The above program prints out:


6 5 4 3 15

DO WHILE

The DO WHILE @ statement repeatedly executes a set of statements while the specified condition is true.

DO [ s [,]] WHILE (e)

Parameter 

Description 

s

Label of an executable statement 

e

Logical expression  

Description

Execution proceeds as follows:

  1. The specified expression is evaluated.

  2. If the value of the expression is true, the statements in the range of the DO WHILE loop are executed.

  3. If the value of the expression is false, control is transferred to the statement following the DO WHILE loop.

Terminal Statement

If s is specified, the statement identified by it is called the terminal statement, and it must follow the DO WHILE statement. The terminal statement must not be one of the following statements:

If the terminal statement is a logical IF statement, it can contain any executable statement, except:

If s is not specified, the DO WHILE loop must end with an END DO statement.

DO WHILE Loop Range

The range of a DO WHILE loop consists of all the executable statements that appear following the DO WHILE statement, up to and including the terminal statement.

If a DO WHILE statement appears within the range of another DO WHILE loop, its range must be entirely contained within the range of the outer DO WHILE loop. More than one DO WHILE loop can have the same terminal statement.

If a DO WHILE statement appears within an IF, ELSE IF, or ELSE block, the range of the associated DO WHILE loop must be entirely within that block.

If a block IF statement appears within the range of a DO WHILE loop, the corresponding END IF statement must also appear within the range of that DO WHILE loop.

Terminal Statement Processing

After the terminal statement of a DO WHILE loop is executed, control is transferred back to the corresponding DO WHILE statement.

Restrictions

Jumping into the range of a DO WHILE loop from outside its range can produce unpredictable results.

Comments

The variables used in the e can be modified in any way within the range of the DO WHILE loop.

Examples

Example 1: A DO WHILE without a statement number:


       INTEGER A(4,4), C, R 
       ... 
       C = 4 
       R = 1 
       DO WHILE ( C .GT. R ) 
              A(C,R) = 1 
              C = C - 1 
       END DO 

Example 2: A DO WHILE with a statement number:


       INTEGER A(4,4), C, R 
       ... 
       DO 10 WHILE ( C .NE. R ) 
              A(C,R) = A(C,R) + 1 
       C = C+1 
10     CONTINUE

DOUBLE COMPLEX

The DOUBLE COMPLEX @ statement specifies the type to be double complex. It optionally specifies array dimensions and size, and initializes with values.

DOUBLE COMPLEX v[/c/] [, v[/c/] ...

Parameter 

Description 

v

Name of a symbolic constant, variable, array, array declarator, function, or dummy function  

c

List of constants for the immediately preceding name  

Description

The declaration can be: DOUBLE COMPLEX or COMPLEX*16.

DOUBLE COMPLEX @

For a declaration such as DOUBLE COMPLEX Z, the variable Z is two REAL*8 elements contiguous in memory, interpreted as one double-width complex number.

If you do not specify the size, a default size is used.

The default size, for a declaration such as DOUBLE COMPLEX Z, can be altered by compiling with any of the options -dbl, -r8, or -xtypemap. See the discussion in Chapter 2 for details.

COMPLEX*16 @

For a declaration such as COMPLEX*16 Z, the variable Z is always two REAL*8 elements contiguous in memory, interpreted as one double-width complex number.

Comments

There is a double-complex version of each complex built-in function. Generally, the specific function names begin with Z or CD instead of C, except for the two functions, DIMAG and DREAL, which return a real value. Examples are: SIN(), CSIN(), CDSIN().

Example: Double-complex scalars and arrays:


       DOUBLE COMPLEX U, V 
       DOUBLE COMPLEX W(3,6) 
       COMPLEX*16 X, Y(5,5)
       COMPLEX  U*16(5), V(5)*16

DOUBLE PRECISION

The DOUBLE PRECISION statement specifies the type to be double precision, and optionally specifies array dimensions and initializes with values.

DOUBLE PRECISION v[/c/] [, v[/c/] ...

Parameter 

Description 

v

Name of a symbolic constant, variable, array, array declarator, function, or dummy function 

c

List of constants for the immediately preceding name  

Description

The declaration can be: DOUBLE PRECISION or REAL*8.

DOUBLE PRECISION

For a declaration such as DOUBLE PRECISION X, the variable X is a REAL*8 element in memory, interpreted as one double-width real number.

If you do not specify the size, a default size is used. The default size, for a declaration such as DOUBLE PRECISION X, can be altered by compiling with any of the options -dbl, -r8, or -xtypemap. See the discussion in Chapter 2 for details.

REAL*8 @

For a declaration such as REAL*8 X, the variable X is always an element of type REAL*8 in memory, interpreted as a double-width real number.

Example

For example:


       DOUBLE PRECISION R, S(3,6)
       REAL*8 T(-1:0,5)

ELSE

The ELSE statement indicates the beginning of an ELSE block.

IF (e) THEN

...

ELSE

...

END IF

where e is a logical expression.

Description

Execution of an ELSE statement has no effect on the program.

An ELSE block consists of all the executable statements following the ELSE statements, up to but not including the next END IF statement at the same IF level as the ELSE statement. See "IF (Block)" for more information.

An ELSE block can be empty.

Restrictions

You cannot jump into an ELSE block from outside the ELSE block.

The statement label, if any, of an ELSE statement cannot be referenced by any statement.

A matching END IF statement of the same IF level as the ELSE must appear before any ELSE IF or ELSE statement at the same IF level.

Examples

Example 1: ELSE:


       CHARACTER S 
       ... 
       IF ( S .GE. '0' .AND. S .LE. '9' ) THEN 
              CALL PUSH 
       ELSE 
              CALL TOLOWER 
       END IF 
       ... 

Example 2: An invalid ELSE IF where an END IF is expected:


       IF ( K .GT. 5 ) THEN 
              N = 1 
       ELSE 
              N = 0 
       ELSE IF ( K .EQ. 5 ) THEN 	           Incorrect 
       ... 

ELSE IF

The ELSE IF provides a multiple alternative decision structure.

ELSE IF (e2) THEN

IF (e1) THEN

END IF

where e1 and e2 are logical expressions.

Description

You can make a series of independent tests, and each test can have its own sequence of statements.

An ELSE IF block consists of all the executable statements following the ELSE IF statement up to, but not including, the next ELSE IF, ELSE, or END IF statement at the same IF level as the ELSE IF statement.

An ELSE IF block can be empty.

Execution of the ELSE IF (e) proceeds as follows, depending on the value of the logical expression, e:

  1. e is evaluated.

  2. If e is true, execution continues with the first statement of the ELSE IF block. If e is true and the ELSE IF block is empty, control is transferred to the next END IF statement at the same IF level as the ELSE IF statement.

  3. If e is false, control is transferred to the next ELSE IF, ELSE, or END IF statement at the same IF level as the ELSE IF statement.

Restrictions

You cannot jump into an ELSE IF block from outside the ELSE IF block.

The statement label, if any, of an ELSE IF statement cannot be referenced by any statement.

A matching END IF statement of the same IF level as the ELSE IF must appear before any ELSE IF or ELSE statement at the same IF level.

Example

Example: ELSE IF:


       READ (*,*) N 
       IF ( N .LT. 0 ) THEN 
              WRITE(*,*) 'N<0'
       ELSE IF ( N .EQ. 0) THEN
              WRITE(*,*) 'N=0' 
       ELSE
              WRITE(*,*) 'N>0'
       END IF 

ENCODE/DECODE

The ENCODE @ statement writes data from a list to memory.

ENCODE(size, f, buf [, IOSTAT=ios] [, ERR=s]) [iolist]

Parameter 

Description 

size

 Number of characters to be translated

f

 Format identifier

buf

 Variable, array, or array element

ios

 I/O status specifier

s

 Error specifier (statement label)

iolist

 List of I/O items, each a character variable, array, or array element

Description

ENCODE is provided for compatibility with older versions of FORTRAN. Similar functionality can be accomplished using internal files with a formatted sequential WRITE statement. ENCODE is not in the FORTRAN 77 Standard.

Data are edited according to the format identifier.

Example


       CHARACTER S*6, T*6 
       INTEGER V(3)*4 
       DATA S / '987654' / 
       DECODE( 6, 1, S ) V 
1      FORMAT( 3 I2 ) 
       ENCODE( 6, 1, T ) V(3), V(2), V(1) 

The DECODE reads the characters of S as 3 integers, and stores them into V(1), V(2), and V(3). The ENCODE statement writes the values V(3), V(2), and V(1), into T as characters; T then contains '547698'.

See "DECODE/ENCODE" for more information and a full example.

END

The END statement indicates the end of a program unit with the following syntax:

END

Description

The END statement:

In a main program, an END statement terminates the execution of the program. In a function or subroutine, it has the effect of a RETURN. @

In the FORTRAN 77 Standard, the END statement cannot be continued, but f77 allows this practice. @

No other statement, such as an END IF statement, can have an initial line that appears to be an END statement.

Example

Example: END:


       PROGRAM MAIN 
       WRITE( *, * ) 'Very little' 
       END 

END DO

The END DO @ statement terminates a DO loop and requires the following syntax:

END DO

Description

The END DO statement is the delimiting statement of a Block DO statement. If the statement label is not specified in a DO statement, the corresponding terminating statement must be an END DO statement. You can branch to an END DO statement only from within the range of the DO loop that it terminates.

Examples

Example 1: A DO loop with a statement number:


       DO 10 N = 1, 100 
              ... 
10     END DO 

Example 2: A DO loop without statement number:


       DO N = 1, 100 
       ... 
       END DO 

END FILE

The END FILE statement writes an end-of-file record as the next record of the file connected to the specified unit.

END FILE u

END FILE ([UNIT= ] u [, IOSTAT=ios] [, ERR=s])

Parameter 

Description 

u

Unit identifier of an external unit connected to the file. The options can be specified in any order, but if UNIT= is omitted, then u must be first.

iost

I/O status specifier, an integer variable or an integer array element.  

s

Error specifier, s must be the label of an executable statement in the same program in which the END FILE statement occurs. The program control is transferred to the label in the event of an error during the execution of the END FILE statement.

Description

If you are using the ENDFILE statement and other standard FORTRAN I/O for tapes, we recommend that you use the TOPEN() routines instead, because they are more reliable.

Two endfile records signify the end-of-tape mark. When writing to a tape file, ENDFILE writes two endfile records, then the tape backspaces over the second one. If the file is closed at this point, both end-of-file and end-of-tape are marked. If more records are written at this point, either by continued write statements or by another program if you are using no-rewind magnetic tape, the first tape mark stands (endfile record), and is followed by another data file, then by more tape marks, and so on.

Restrictions

u must be connected for sequential access. Execution of an END FILE statement on a direct-access file is not defined in the FORTRAN 77 Standard, and is unpredictable. Do not use an END FILE statement on a direct-access file.

Examples

Example 1: Constants:


       END FILE 2 
       END FILE ( 2 ) 
       END FILE ( UNIT=2 ) 

Example 2: Variables:


       LOGUNIT = 2 
       END FILE LOGUNIT 
       END FILE ( LOGUNIT ) 
       END FILE ( UNIT=LOGUNIT )

Example 3: Error trap:


       NOUT = 2 
       END FILE ( UNIT=NOUT, IOSTAT=KODE, ERR=9) 
       ... 
9      WRITE(*,*) 'Error at END FILE, on unit', NOUT 
       STOP

END IF

The END IF statement ends the block IF that the IF began and requires the following syntax:

END IF

Description

For each block IF statement there must be a corresponding END IF statement in the same program unit. An END IF statement matches if it is at the same IF level as the block IF statement.

Examples

Example 1: IF/END IF


       IF ( N .GT. 0 )THEN
              N = N+1
       END IF

:

Example 2: IF/ELSE/END IF:


       IF ( N .EQ. 0 ) THEN
              N = N+1
       ELSE
              N = N-1
       END IF 

END MAP

The END MAP @ statement terminates the MAP declaration and requires the following syntax:

END MAP

Description

See "UNION and MAP" for more information.

Restrictions

The MAP statement must be within a UNION statement.

Example


       ...
       MAP 
              CHARACTER *16 MAJOR 
       END MAP 
       ...

END STRUCTURE

The END STRUCTURE @ statement terminates the STRUCTURE statement and requires the following syntax:

END STRUCTURE

Description

See "STRUCTURE" for more information.

Example


       STRUCTURE /PROD/ 
              INTEGER*4					ID 
              CHARACTER*16							NAME 
              CHARACTER*8							MODEL 
              REAL*4					COST 
              REAL*4					PRICE 
       END STRUCTURE 

END UNION

The END UNION @ statement terminates the UNION statement and requires the following syntax:

END UNION

Description

See "UNION and MAP" for more information.

Example


       UNION 
       MAP 
              CHARACTER*16 
       END MAP 
       MAP 
              INTEGER*2    CREDITS 
              CHARACTER *8 GRAD_DATE 
       END MAP 
       END UNION 

ENTRY

The ENTRY statement defines an alternate entry point within a subprogram.

ENTRY en [([fa[, fa]])]

Parameter 

Description 

en

 Symbolic name of an entry point in a function or subroutine subprogram

fa

 Formal argument--it can be a variable name, array name, formal procedure name, or an asterisk specifying an alternate return label.

Description

Note these nuances for the ENTRY statement:

Procedure References by Entry Names

An ENTRY name used in a subroutine subprogram is treated like a subroutine and can be referenced with a CALL statement. Similarly, the ENTRY name used in a function subprogram is treated like a function and can be referenced as a function reference.

An entry name can be specified in an EXTERNAL statement and used as an actual argument. It cannot be used as a dummy argument.

Execution of an ENTRY subprogram (subroutine or function) begins with the first executable statement after the ENTRY statement.

The ENTRY statement is a nonexecutable statement.

The entry name cannot be used in the executable statements that physically precede the appearance of the entry name in an ENTRY statement.

Argument Correspondence

The formal arguments of an ENTRY statement need not be the same in order, number, type, and name as those for FUNCTION, SUBROUTINE, and other ENTRY statements in the same subprogram. Each reference to a function, subroutine, or entry must use an actual argument list that agrees in order, number, type, and name with the dummy argument list in the corresponding FUNCTION, SUBROUTINE, or ENTRY statement.

Alternate return arguments in ENTRY statements can be specified by placing asterisks in the dummy argument list. Ampersands are valid alternates. @ ENTRY statements that specify alternate return arguments can be used only in subroutine subprograms, not functions.

Restrictions

An ENTRY statement cannot be used within a block IF construct or a DO loop.

If an ENTRY statement appears in a character function subprogram, it must be defined as type CHARACTER with the same length as that of a function subprogram.

Examples

Example 1: Multiple entry points in a subroutine


       SUBROUTINE FIN( A, B, C ) 
       INTEGER A, B 
       CHARACTER C*4 
       ... 
       RETURN 

       ENTRY HLEP( A, B, C ) 
       ... 
       RETURN 

       ENTRY MOOZ 
       ... 
       RETURN 
       END 

:

In the above example, the subroutine FIN has two alternate entries: the entry HLEP has an argument list; the entry MOOZ has no argument list.

Example 2: In the calling routine, you can call the above subroutine and entries as follows:


       INTEGER A, B 
       CHARACTER C*4 
       ... 
       CALL FIN( A, B, C ) 
       ... 
       CALL MOOZ 
       ... 
       CALL HLEP( A, B, C ) 
       ... 

In the above example, the order of the call statements need not match the order of the entry statements.

Example 3: Multiple entry points in a function:


       REAL FUNCTION F2 ( X ) 
       F2 = 2.0 * X 
       RETURN 

       ENTRY F3 ( X ) 
       F3 = 3.0 * X 
       RETURN 

       ENTRY FHALF ( X ) 
       FHALF = X / 2.0 
       RETURN 
       END 

EQUIVALENCE

The EQUIVALENCE statement specifies that two or more variables or arrays in a program unit share the same memory.

EQUIVALENCE (nlist) [, (nlist)] ...

Parameter 

Description 

nlist

List of variable names, array element names, array names, and character substring names separated by commas  

Description

An EQUIVALENCE statement stipulates that the storage sequence of the entities whose names appear in the list nlist must have the same first memory location.

An EQUIVALENCE statement can cause association of entities other than specified in the nlist.

An array name, if present, refers to the first element of the array.

If an array element name appears in an EQUIVALENCE statement, the number of subscripts can be less than or equal to the number of dimensions specified in the array declarator for the array name.

Restrictions

In nlist, dummy arguments and functions are not permitted.

Subscripts of array elements must be integer constants greater than the lower bound and less than or equal to the upper bound.

EQUIVALENCE can associate automatic variables only with other automatic variables or undefined storage classes. These classes must be ones which are not in any of the COMMON, STATIC, SAVE, DATA, or dummy arguments.

An EQUIVALENCE statement can associate an element of type character with a noncharacter element. @

An EQUIVALENCE statement cannot specify that the same storage unit is to occur more than once in a storage sequence. For example, the following statement is not allowed:


       DIMENSION A (2) 
       EQUIVALENCE (A(1),B), (A(2),B) 

An EQUIVALENCE statement cannot specify that consecutive storage units are to be nonconsecutive. For example, the following statement is not allowed:


       REAL A (2) 
       DOUBLE PRECISION D (2) 
       EQUIVALENCE (A(1), D(1)), (A(2), D(2)) 

When COMMON statements and EQUIVALENCE statements are used together, several additional rules can apply. For such rules, refer to the notes on the COMMON statement.

Example


       CHARACTER A*4, B*4, C(2)*3 
       EQUIVALENCE (A,C(1)),(B,C(2))

The association of A, B, and C can be graphically illustrated as follows. The first seven character positions are arranged in memory as follows:

 

         01 

        02 

         03 

         04 

        05 

        06 

        07 

       A(1) 

       A(2) 

        A(3) 

       A(4) 

 

 

 

 

 

 

 

 

 

 

 

 

 

 

       B(1) 

        B(2) 

       B(3) 

       B(4) 

 

 

 

 

 

 

 

 

     C(1)(1) 

     C(1)(2) 

     C(1)(3) 

     C(2)(1) 

     C(2)(2) 

     C(2)(3) 

 

EXTERNAL

The EXTERNAL statement specifies procedures or dummy procedures as external, and allows their symbolic names to be used as actual arguments.

EXTERNAL proc [, proc] ...

Parameter 

Description 

proc

Name of external procedure, dummy procedure, or block data routine. 

Description

If an external procedure or a dummy procedure is an actual argument, it must be in an EXTERNAL statement in the same program unit.

If an intrinsic function name appears in an EXTERNAL statement, that name refers to some external subroutine or function. The corresponding intrinsic function is not available in the program unit.

Restrictions

A subroutine or function name can appear in only one of the EXTERNAL statements of a program unit.

A statement function name must not appear in an EXTERNAL statement.

Examples

Example 1: Use your own version of TAN:


       EXTERNAL TAN 
       T = TAN( 45.0 ) 
       ... 
       END 
       FUNCTION TAN( X ) 
       ... 
       RETURN 
       END 

Example 2: Pass a user-defined function name as an argument:


       REAL AREA, LOW, HIGH 
       EXTERNAL FCN 
       ... 
       CALL RUNGE ( FCN, LOW, HIGH, AREA ) 
       ... 
       END 

       FUNCTION FCN( X ) 
       ... 
       RETURN 
       END 

       SUBROUTINE RUNGE ( F, X0, X1, A ) 
       ... 
       RETURN 
       END

FORMAT

The FORMAT statement specifies the layout of the input or output records.

label FORMAT (f)

Parameter 

Description 

label

Statement number 

f

Format specification list  

The items in f have the form: label FORMAT ( f )

[r] desc

[r] (f)

r

A repeat factor 

desc

An edit descriptor (repeatable or nonrepeatable). If r is present, then d must be repeatable.

The repeatable edit descriptors are:

I

Iw

Iw.d

O

Ow

Ow.d

Z

Zw

Zw.d

F

Fw

Fw.d

A

Aw

L

Lw

E

Ew

Ew.d

Ew.d.e

Eew.dE

D

Dw

Dw.d

Dw.d.e

Dw.dEe

G

Gw

Gw.d

Gw.d.e

Gw.dEe

Here is a summary:

The nonrepeatable edit descriptors are:

See "Formatted I/O" for full details of these edit descriptors.

Description

The FORMAT statement includes the explicit editing directives to produce or use the layout of the record. It is used with formatted input/output statements and ENCODE/DECODE statements.

Repeat Factor

r must be a nonzero, unsigned, integer constant.

Repeatable Edit Descriptors

The descriptors I, O, Z, F, E, D, G, L, and A indicate the manner of editing and are repeatable.

w and e are nonzero, unsigned integer constants.

d and m are unsigned integer constants.

Nonrepeatable Edit Descriptors

The descriptors are the following:

("), ($), ('), (/), (:), B, BN, BZ, H, P, R, Q, S, SU, SP, SS, T, TL, TR, X

These descriptors indicate the manner of editing and are not repeatable:

Item Separator

Items in the format specification list are separated by commas. A comma can be omitted before or after the slash and colon edit descriptors, between a P edit descriptor, and the immediately following F, E, D, or G edit descriptors.

In some sense, the comma can be omitted anywhere the meaning is clear without it, but, other than those cases listed above, this is nonstandard. u

Variable Format Expressions @

In general, any integer constant in a format can be replaced by an arbitrary expression enclosed in angle brackets:

1 FORMAT( < e > )

The n in an nH... edit descriptor cannot be a variable format expression.

Restrictions

The FORMAT statement label cannot be used in a GO TO, IF-arithmetic, DO, or alternate return.

Warnings

For explicit formats, invalid format strings cause warnings or error messages at compile time.

For formats in variables, invalid format strings cause warnings or error messages at runtime.

For variable format expressions, of the form <e>, invalid format strings cause warnings or error messages at compile time or runtime.

See "Runtime Formats " for details.

Examples

Example 1: Some A, I, and F formats:


       READ( 2, 1 ) PART, ID, HEIGHT, WEIGHT 
1      FORMAT( A8, 2X, I4, F8.2, F8.2 ) 
       WRITE( 9, 2 ) PART, ID, HEIGHT, WEIGHT 
2      FORMAT( 'Part:', A8, ' Id:', I4, ' Height:', F8.2, 
&           ' Weight:', F8.2 ) 

Example 2: Variable format expressions:


       DO 100 N = 1, 50 
       ... 
1      FORMAT( 2X, F<N+1>.2 ) 

FUNCTION (External)

The FUNCTION statement identifies a program unit as a function subprogram.

[type] FUNCTION fun ([ar[, ar]])  

Parameter 

Description 

type

BYTE @

CHARACTER

CHARACTER*n (where n must be greater than zero)

CHARACTER*(*)

COMPLEX

COMPLEX*8 @

COMPLEX*16 @

COMPLEX*32 @

DOUBLE COMPLEX @

DOUBLE PRECISION

INTEGER

INTEGER*2 @

INTEGER*4 @

INTEGER*8 @

LOGICAL

LOGICAL*1 @

LOGICAL*2 @

LOGICAL*4 @

LOGICAL*8 @

REAL

REAL*4 @

REAL*8 @

REAL*16 @

fun

Symbolic name assigned to function 

ar

Formal argument name  

(COMPLEX*32 and REAL*16 are SPARC only.)

An alternate nonstandard syntax for length specifier is as follows: @

[ type ] FUNCTION name [* m]([ ar [,ar] ])

Parameter 

Description 

m

Unsigned, nonzero integer constant specifying length of the data type. 

ar

Formal argument name  

Description

Note the type, value, and formal arguments for a FUNCTION statement.

Type of Function

The function statement involves type, name, and formal arguments.

If type is not present in the FUNCTION statement, then the type of the function is determined by default and by any subsequent IMPLICIT or type statement. If type is present, then the function name cannot appear in other type statements.


Note -

Compiling with any of the options -dbl, -r8, -i2, or -xtypemap can alter the default data size assumed in the call to or definition of functions unless the data type size is explicitly declared. See Chapter 2 and the Fortran User Guide for details on these options.


Value of Function

The symbolic name of the function must appear as a variable name in the subprogram. The value of this variable, at the time of execution of the RETURN or END statement in the function subprogram, is the value of the function.

Formal Arguments

The list of arguments defines the number of formal arguments. The type of these formal arguments is defined by some combination of default, type statements, IMPLICIT statements, and DIMENSION statements.

The number of formal arguments must be the same as the number of actual arguments at the invocation of this function subprogram.

A function can assign values to formal arguments. These values are returned to the calling program when the RETURN or END statements are executed in the function subprogram.

Restrictions

Alternate return specifiers are not allowed in FUNCTION statements.

f77 provides recursive calls. A function or subroutine is called recursively if it calls itself directly. If it calls another function or subroutine, which in turn calls this function or subroutine before returning, then it is also called recursively.

Examples

Example 1: Character function:


       CHARACTER*5 FUNCTION BOOL(ARG) 
       BOOL = 'TRUE' 
       IF (ARG .LE. 0) BOOL = 'FALSE' 
       RETURN 
       END 

In the above example, BOOL is defined as a function of type CHARACTER with a length of 5 characters. This function when called returns the string, TRUE or FALSE, depending on the value of the variable, ARG.

Example 2: Real function:


       FUNCTION SQR (A) 
       SQR = A*A 
       RETURN 
       END 

In the above example, the function SQR is defined as function of type REAL by default, and returns the square of the number passed to it.

Example 3: Size of function, alternate syntax: @


       INTEGER FUNCTION FCN*2 ( A, B, C ) 

The above nonstandard form is treated as:


       INTEGER*2 FUNCTION FCN ( A, B, C ) 

GO TO (Assigned)

The assigned GO TO statement branches to a statement label identified by the assigned label value of a variable.

GO TO i [[,](s[, s])]

Parameter 

Description 

i

Integer variable name 

s

Statement label of an executable statement 

Description

Execution proceeds as follows:

  1. At the time an assigned GO TO statement is executed, the variable i must have been assigned the label value of an executable statement in the same program unit as the assigned GO TO statement.

  2. If an assigned GO TO statement is executed, control transfers to a statement identified by i.

  3. If a list of statement labels is present, the statement label assigned to i must be one of the labels in the list.

Restrictions

i must be assigned by an ASSIGN statement in the same program unit as the GO TO statement.

i must be INTEGER*4 or INTEGER*8, not INTEGER*2.

s must be in the same program unit as the GO TO statement.

The same statement label can appear more than once in a GO TO statement.

The statement control jumps to must be executable, not DATA, ENTRY, FORMAT, or INCLUDE.

Control cannot jump into a DO, IF, ELSE IF, or ELSE block from outside the block.

Example

Example: Assigned GO TO:


       ASSIGN 10 TO N 
       ... 
       GO TO N ( 10, 20, 30, 40 ) 
       ... 
10     CONTINUE 
       ... 
40     STOP 

GO TO (Computed)

The computed GO TO statement selects one statement label from a list, depending on the value of an integer or real expression, and transfers control to the selected one.

GO TO (s[, s])[,]e

Parameter 

Description 

s

Statement label of an executable statement

e

Expression of type integer or real  

Description

Execution proceeds as follows:

  1. e is evaluated first. It is converted to integer, if required.

  2. If 1 £ e £ n, where n is the number of statement labels specified, then the eth label is selected from the specified list and control is transferred to it.

  3. If the value of e is outside the range, that is, e < 1 or e > n, then the computed GO TO statement serves as a CONTINUE statement.

Restrictions

s must be in the same program unit as the GO TO statement.

The same statement label can appear more than once in a GO TO statement.

The statement control jumps to must be executable, not DATA, ENTRY, FORMAT, or INCLUDE.

Control cannot jump into a DO, IF, ELSE IF, or ELSE block from outside the block.

Example

Example: Computed GO TO


       ... 
       GO TO ( 10, 20, 30, 40 ), N
       ... 
10   CONTINUE 
       ... 
20   CONTINUE 
       ... 
40   CONTINUE 

:

In the above example:

GO TO (Unconditional)

The unconditional GO TO statement transfers control to a specified statement.

GO TO s

Parameter 

Description 

s

Statement label of an executable statement

Description

Execution of the GO TO statement transfers control to the statement labeled s.

Restrictions

s must be in the same program unit as the GO TO statement.

The statement control jumps to must be executable, not a DATA, ENTRY, FORMAT, or INCLUDE statement.

Control cannot jump into a DO, IF, ELSE IF, or ELSE block from outside the block.

Example


       A = 100.0 
       B = 0.01 
       GO TO 90 
       ... 
90   CONTINUE 

IF (Arithmetic)

The arithmetic IF statement branches to one of three specified statements, depending on the value of an arithmetic expression.

IF (e) s1, s2, s3

Parameter 

Description 

e

 Arithmetic expression: integer, real, double precision, or quadruple precision

s1, s2, s3

Labels of executable statements

Description

The IF statement transfers control to the first, second, or third label if the value of the arithmetic expression is less than zero, equal to zero, or greater than zero, respectively.

The restrictions are:

Example


       N = 0 
       IF ( N ) 10, 20, 30 

Since the value of N is zero, control is transferred to statement label 20.

IF (Block)

The block IF statement executes one of two or more sequences of statements, depending on the value of a logical expression.

IF (e) THEN

END IF

Parameter 

Description 

e

A logical expression  

Description

The block IF statement evaluates a logical expression and, if the logical expression is true, it executes a set of statements called the IF block. If the logical expression is false, control transfers to the next ELSE, ELSE IF, or END IF statement at the same IF-level.

IF Level

The IF level of a statement S is the value n1-n2, where n1 is the number of block IF statements from the beginning of the program unit up to the end, including S; n2 is the number of END IF statements in the program unit up to, but not including, S.

Example: In the following program, the IF-level of statement 9 is 2-1, or, 1


       IF ( X .LT. 0.0 ) THEN 
              MIN = NODE 
       END IF 
       ... 
9      IF ( Y .LT. 0.0 ) THEN 
              MIN = NODE - 1 
       END IF 

:

The IF-level of every statement must be zero or positive. The IF-level of each block IF, ELSE IF, ELSE, and END IF statement must be positive. The IF-level of the END statement of each program unit must be zero.

IF Block

An IF block consists of all the executable statements following the block IF statement, up to, but not including, the next ELSE, ELSE IF, or END IF statement that has the same if level as the block IF statement. An IF block can be empty. In the following example, the two assignment statements form an IF block:


       IF ( X .LT. Y ) THEN 
              M = 0 
              N = N+1 
       END IF

Execution proceeds as follows:

  1. The logical expression e is evaluated first. If e is true, execution continues with the first statement of the IF block.

  2. If e is true and the IF block is empty, control is transferred to the next END IF statement with the same IF level as the block IF statement.

  3. If e is false, control is transferred to the next ELSE IF, ELSE, or END IF statement with the same IF level as the block IF statement.

  4. If the last statement of the IF block does not result in a branch to a label, control is transferred to the next END IF statement that has the same IF level as the block IF statement preceding the IF block.

Restrictions

Control cannot jump into an IF block from outside the IF block.

Examples

Example 1: IF-THEN-ELSE:


       IF ( L ) THEN 
              N=N+1 
              CALL CALC 
       ELSE 
              K=K+1 
              CALL DISP 
       END IF 

Example 2: IF-THEN-ELSE-IF with ELSE-IF:


       IF ( C .EQ. 'a' ) THEN 
              NA=NA+1 
              CALL APPEND 
       ELSE IF ( C .EQ. 'b' ) THEN 
              NB=NB+1 
              CALL BEFORE 
       ELSE IF ( C .EQ. 'c' ) THEN 
              NC=NC+1 
              CALL CENTER 
       END IF

Example 3: Nested IF-THEN-ELSE:


       IF ( PRESSURE .GT 1000.0 ) THEN 
              IF ( N .LT. 0.0 ) THEN 
                     X = 0.0 
                     Y = 0.0 
              ELSE 
                     Z = 0.0 
              END IF 
       ELSE IF ( TEMPERATURE .GT. 547.0 ) THEN 
              Z = 1.0 
       ELSE 
              X = 1.0 
              Y = 1.0 
       END IF 

IF (Logical)

The logical IF statement executes one single statement, or does not execute it, depending on the value of a logical expression.

IF (e) st

Parameter 

Description 

e

Logical expression 

st

Executable statement  

Description

The logical IF statement evaluates a logical expression and executes the specified statement if the value of the logical expression is true. The specified statement is not executed if the value of the logical expression is false, and execution continues as though a CONTINUE statement had been executed.

st can be any executable statement, except a DO block, IF, ELSE IF, ELSE, END IF, END, or another logical IF statement.

Example


       IF ( VALUE .LE. ATAD ) CALL PUNT  ! Note that there is no THEN. 
       IF ( TALLY .GE. 1000 ) RETURN 

IMPLICIT

The IMPLICIT statement confirms or changes the default type of names.

IMPLICIT type (a[, a]) [, type (a[, a])]

IMPLICIT NONE

IMPLICIT UNDEFINED(A-Z) u

Parameter 

Description 

type

BYTE u

CHARACTER

CHARACTER*n (where n must be greater than 0)

CHARACTER*(*)

COMPLEX

COMPLEX*8 u

COMPLEX*16 u

COMPLEX*32 u (SPARC only)

DOUBLE COMPLEX u

DOUBLE PRECISION

INTEGER

INTEGER*2 u

INTEGER*4 u

INTEGER*8 u

LOGICAL

LOGICAL*1 u

LOGICAL*2 u

LOGICAL*4 u

LOGICAL*8 u

REAL

REAL*4 u

REAL*8 u

REAL*16 u (SPARC only)

AUTOMATIC u

STATIC u

a

Either a single letter or a range of single letters in alphabetical order. A range of letters can be specified by the first and last letters of the range, separated by a minus sign.  

Description

The different uses for implicit typing and no implicit typing are described here.

Implicit Typing

The IMPLICIT statement can also indicate that no implicit typing rules apply in a program unit.

An IMPLICIT statement specifies a type and size for all user-defined names that begin with any letter, either a single letter or in a range of letters, appearing in the specification.

An IMPLICIT statement does not change the type of the intrinsic functions.

An IMPLICIT statement applies only to the program unit that contains it.

A program unit can contain more than one IMPLICIT statement.

IMPLICIT types for particular user names are overridden by a type statement.


Note -

Compiling with any of the options -dbl, -i2, -r8, or -xtypemap can alter the assumed size of names typed with an IMPLICIT statement that does not specify a size: IMPLICIT REAL (A-Z). See Chapter 2 and the Fortran User's Guide for details.


No Implicit Typing

The second form of IMPLICIT specifies that no implicit typing should be done for user-defined names, and all user-defined names shall have their types declared explicitly.

If either IMPLICIT NONE or IMPLICIT UNDEFINED (A-Z) is specified, there cannot be any other IMPLICIT statement in the program unit.

Restrictions

IMPLICIT statements must precede all other specification statements.

The same letter can appear more than once as a single letter, or in a range of letters in all IMPLICIT statements of a program unit. @

The FORTRAN 77 Standard restricts this usage to only once. For f77, if a letter is used twice, each usage is declared in order. See Example 4.

Examples

Example 1: IMPLICIT: everything is integer:


       IMPLICIT INTEGER (A-Z) 
       X = 3 
       K = 1 
       STRING = 0 

Example 2: Complex if it starts with U, V, or W; character if it starts with C or S:


       IMPLICIT COMPLEX (U,V,W), CHARACTER*4 (C,S) 
       U1 = ( 1.0, 3.0) 
       STRING = 'abcd'
       I = 0 
       X = 0.0 

Example 3: All items must be declared:


       IMPLICIT NONE 
       CHARACTER STR*8 
       INTEGER N 
       REAL Y 
       N = 100 
       Y = 1.0E5 
       STR = 'Length'

In the above example, once IMPLICIT NONE is specified in the beginning. All the variables must be declared explicitly.

Example 4: A letter used twice: @


       IMPLICIT INTEGER (A-Z)
       IMPLICIT REAL (A-C)
       C = 1.5E8
       D = 9

In the above example, D through Z implies INTEGER, and A through C implies REAL.

INCLUDE

The INCLUDE @ statement inserts a file into the source program.

INCLUDE 'file'

Parameter 

Description 

file

Name of the file to be inserted 

INCLUDE "file"

Description

The contents of the named file replace the INCLUDE statement.

Search Path

If the name referred to by the INCLUDE statement begins with the character /, then it is taken by f77 to mean the absolute path name of the INCLUDE file. Otherwise, f77 looks for the file in the following directories, in this order:

  1. The directory that contains the source file with the INCLUDE statement

  2. The directories that are named in the -Iloc options

  3. The current directory in which the f77 command was issued

  4. The directories in the default list. For a standard install, the default list is:

    /opt/SUNWspro/SC5.0/include/f77 /usr/include

    For a non-standard install to a directory /mydir/, the default list is:

    /mydir/SUNWspro/SC5.0/include/f77 /usr/include

The release number, SC5.0, varies with the release of the set of compilers.

These INCLUDE statements can be nested ten deep.

Preprocessor #include

The paths and order searched for the INCLUDE statement are not the same as those searched for the preprocessor #include directive, described under -I in the Fortran User's Guide. Files included by the preprocessor #include directive can contain #defines and the like; files included with the compiler INCLUDE statement must contain only FORTRAN statements.

VMS Logical File Names in the INCLUDE Statement

f77 interprets VMS logical file names on the INCLUDE statement if:

Examples

Example 1: INCLUDE, simple case:


       INCLUDE 'stuff'

The above line is replaced by the contents of the file stuff.

Example 2: INCLUDE, search paths:

For the following conditions:

In this example, f77 seeks const.h in these directories, in the order shown.

For a standard install, f77 searches these directories:

For a non-standard install to a directory /mydir, it searches these directories:

INQUIRE

The INQUIRE statement returns information about a unit or file.

INQUIRE([UNIT =] u, slist)

INQUIRE(FILE = fn, slist)

Parameter 

Description 

fn

Name of the file being queried  

u

Number of the file being queried  

slist

The specifiers list slist can include one or more of the following, in any order:

  • ERR = s

  • EXIST = ex

  • OPENED = od

  • NAMED = nmd

  • ACCESS = acc

  • SEQUENTIAL = seq

  • DIRECT = dir

  • FORM = fm

  • FORMATTED = fmt

  • UNFORMATTED = unf

  • NAME = fn

  • BLANK = blnk

  • IOSTAT = ios

  • NUMBER = num

  • RECL = rcl

  • NEXTREC = nr

Description

You can determine such things about a file as whether it exists, is opened, or is connected for sequential I/O. That is, files have such attributes as name, existence (or nonexistence), and the ability to be connected in certain ways (FORMATTED, UNFORMATTED, SEQUENTIAL, or DIRECT).

Inquire either by unit or by file, but not by both in the same statement.

In this system environment, the only way to discover what permissions you have for a file is to use the ACCESS(3F) function. The INQUIRE statement does not determine permissions.

The following table summarizes the INQUIRE specifiers:

Table 4-1 INQUIRE Specifiers Summary

Form: SPECIFIER = Variable 

SPECIFIER 

Value of Variable  

Data Type of Variable 

ACCESS

'DIRECT' 'SEQUENTIAL'

CHARACTER

BLANK

'NULL'

'ZERO'

CHARACTER

DIRECT *

'YES' 'NO' 'UNKNOWN'

CHARACTER

ERR

Statement number  

INTEGER

EXIST

.TRUE.

.FALSE.

LOGICAL

FORM

'FORMATTED' 'UNFORMATTED'

CHARACTER

FORMATTED *

'YES' 'NO' 'UNKNOWN'

CHARACTER

IOSTAT

Error number 

INTEGER

NAME

Name of the file 

CHARACTER

NAMED

.TRUE.

.FALSE.

LOGICAL

NEXTREC

Next record number 

INTEGER

NUMBER *

Unit number 

INTEGER

OPENED

.TRUE.

.FALSE.

LOGICAL

RECL

Record length 

INTEGER

SEQUENTIAL *

'YES' 'NO' 'UNKNOWN'

CHARACTER

UNFORMATTED *

'YES' 'NO' 'UNKNOWN'

CHARACTER

* indicates non-standard for inquire-by-unit, but accepted by f77. indicates non-standard for inquire-by-file, but accepted by f77.

Also:

INQUIRE Specifier Keywords

The following provides a detailed list of the INQUIRE specifier keywords:

ACCESS=acc

BLANK=blnk

DIRECT=dir

ERR=s

EXIST=ex

FILE=fn

FORM=fm

FORMATTED=fmt

IOSTAT=ios

NAME=fn

NAMED=nmd

NEXTREC=nr

NUMBER=num

OPENED=od

RECL=rcl

SEQUENTIAL=seq

UNFORMATTED=unf

UNIT=u

Examples

Example 1: Inquire by unit:


       LOGICAL OK 
       INQUIRE( UNIT=3, OPENED=OK ) 
       IF ( OK ) CALL GETSTD ( 3, STDS ) 

Example 2: Inquire by file:


       LOGICAL THERE 
       INQUIRE( FILE='.profile', EXIST=THERE ) 
       IF ( THERE ) CALL GETPROFILE( FC, PROFILE ) 

Example 3: More than one answer, omitting the UNIT=:


       CHARACTER FN*32 
       LOGICAL HASNAME, OK 
       INQUIRE ( 3, OPENED=OK, NAMED=HASNAME, NAME=FN ) 
       IF ( OK .AND. HASNAME ) PRINT *, 'Filename="', FN, '"' 

INTEGER

The INTEGER statement specifies the type to be integer for a symbolic constant, variable, array, function, or dummy function.

Optionally, it specifies array dimensions and size and initializes with values.

INTEGER [*len[,]] v[* len[/c/]] [, v[*len[/c/]] ...

Parameter 

Description 

v

Name of a symbolic constant, variable, array, array declarator, function, or dummy function  

len

Either 2, 4, or 8, the length in bytes of the symbolic constant, variable, array element, or function. 

c

List of constants for the immediately preceding name 

Description

The declarations can be: INTEGER, INTEGER*2, INTEGER*4, INTEGER*8.

INTEGER

For a declaration such as INTEGER H, the variable H is usually one INTEGER*4 element in memory, interpreted as a single integer number. Specifying the size is nonstandard. @

If you do not specify the size, a default size is used. The default size, for a declaration such as INTEGER H, can be altered by compiling with any of the options -dbl, -i2, -r8, or -xtypemap. See the discussion in Chapter 2 for details.

INTEGER*2 @

For a declaration such as INTEGER*2 H, the variable H is always an INTEGER*2 element in memory, interpreted as a single integer number.

INTEGER*4 @

For a declaration such as INTEGER*4 H, the variable H is always an INTEGER*4 element in memory, interpreted as a single integer number.

INTEGER*8 @

For a declaration such as INTEGER*8 H, the variable H is always an INTEGER*8 element in memory, interpreted as a single integer number.

Restrictions

Do not use INTEGER*8 variables or 8-byte constants or expressions when indexing arrays, otherwise, only 4 low-order bytes are taken into account. This action can cause unpredictable results in your program if the index value exceeds the range for 4-byte integers.

Examples

Example 1: Each of these integer declarations are equivalent:


       INTEGER U, V(9) 
       INTEGER*4 U, V(9) 
       INTEGER U*4, V(9)*4 

Example 2: Initialize:


       INTEGER U / 1 /, V / 4 /, W*2 / 1 /, X*2 / 4 / 

INTRINSIC

The INTRINSIC statement lists intrinsic functions that can be passed as actual arguments.

INTRINSIC fun [, fun] ...

Parameter 

Description 

fun

Function name  

Description

If the name of an intrinsic function is used as an actual argument, it must appear in an INTRINSIC statement in the same program unit.

Example: Intrinsic functions passed as actual arguments:


       INTRINSIC SIN, COS 
       X = CALC ( SIN, COS ) 

Restrictions

A symbolic name must not appear in both an EXTERNAL and an INTRINSIC statement in the same program unit.

The actual argument must be a specific name. Most generic names are also specific, but a few are not: IMAG, LOG, and LOG10.

A symbolic name can appear more than once in an INTRINSIC statement.In the FORTRAN 77 Standard, a symbolic name can appear only once in an INTRINSIC statement. @

Because they are in-line or generic, the following intrinsics cannot be passed as actual arguments:

Table 4-2 Intrinsics That Cannot Be Passed As Actual Arguments

LOC

AND

IAND

IIAND

JIAND

OR

IOR

IIOR

IEOR

IIEOR

JIOR

JIEOR

NOT

INOT

JNOT

XOR

LSHIFT

RSHIFT

LRSHIFT

INT

IINT

JINT

IQINT

IIQINT

JIQINT

IFIX

IIFIX

JIFIX

IDINT

IIDINT

JIDINT

FLOAT

FLOATI

FLOATJ

DFLOAT

DFLOTI

DFLOTJ

IZTEXT

SNGL

SNGLQ

REAL

DREAL

DBLE

DBLEQ

QEXT

QEXTD

QFLOAT

CMPLX

DCMPLX

ICHAR

IACHAR

ACHAR

CHAR

MAX

MAX0

AMAX0

JZTEXT

AIMAX0

AJMAX0

IMAX0

JMAX0

MAX1

AMAX1

DMAX1

IMAX1

JMAX1

QMAX1

MIN

MIN0

AMIN0

AIMIN0

AJMIN0

IMIN0

JMIN0

MIN1

ZEXT

AMIN1

DMIN1

IMIN1

JMIN1

QMIN1

IMAG

LOG

LOG10

QREAL

QCMPLX

SIZEOF

EPBASE

EPEMAX

EPEMIN

EPHUGE

EPMRSP

EPPREC

EPTINY

LOGICAL

The LOGICAL statement specifies the type to be logical for a symbolic constant, variable, array, function, or dummy function.

Optionally, it specifies array dimensions and initializes with values.

LOGICAL [*len[,]] v[*len[/c/]] [, v[*len[/c/]] ...

Parameter 

Description 

v

Name of a symbolic constant, variable, array, array declarator, function, or dummy function  

len

Either 1, 2, 4, or 8, the length in bytes of the symbolic constant, variable, array element, or function. 8 is allowed only if -dbl is on. @

c

List of constants for the immediately preceding name  

Description

The declarations can be: LOGICAL, LOGICAL*1, LOGICAL*2, LOGICAL*4, LOGICAL*8.

LOGICAL

For a declaration such as LOGICAL H, the variable H is usually one INTEGER*4 element in memory, interpreted as a single logical value. Specifying the size is nonstandard. @

If you do not specify the size, a default size is used. The default size, for a declaration such as LOGICAL Z, can be altered by compiling with any of the options -dbl, -i2,-r8, or -xtypemap. See the discussion in Chapter 2 for details.

LOGICAL*1 @

For a declaration such as LOGICAL*1 H, the variable H is always an BYTE element in memory, interpreted as a single logical value.

LOGICAL*2 @

For a declaration such as LOGICAL*2 H, the variable H is always an INTEGER*2 element in memory, interpreted as a single logical value.

LOGICAL*4 @

For a declaration such as LOGICAL*4 H, the variable H is always an INTEGER*4 element in memory, interpreted as a single logical value.

LOGICAL*8 @

For a declaration such as LOGICAL*8 H, the variable H is always an INTEGER*8 element in memory, interpreted as a single logical value.

Examples

Example 1: Each of these declarations are equivalent:


       LOGICAL U, V(9) 
       LOGICAL*4 U, V(9) 
       LOGICAL U*4, V(9)*4 

Example 2: Initialize:


       LOGICAL U /.false./, V /0/, W*4 /.true./, X*4 /'z'/ 

MAP

The MAP @ declaration defines alternate groups of fields in a union.


       MAP
              field-declaration 
              
              [field-declaration
]
       END MAP

Description

Each field declaration can be one of the following:

Example

Example: MAP:


       STRUCTURE /STUDENT/ 
       CHARACTER*32  NAME 
              INTEGER*2  CLASS 
              UNION 
                     MAP 
                            CHARACTER*16 MAJOR 
                     END MAP 
                     MAP 
                            INTEGER*2  CREDITS 
                            CHARACTER*8  GRAD_DATE 
                     END MAP 
              END UNION 
       END STRUCTURE

NAMELIST

The NAMELIST @ statement defines a list of variables or array names, and associates it with a unique group name.

NAMELIST / grname / namelist [[,] / grname / namelist ] ...

Parameter 

Description 

grname

Symbolic name of the group 

namelist

List of variables and arrays  

Description

The NAMELIST statement contains a group name and other items.

Group Name

The group name is used in the namelist-directed I/O statement to identify the list of variables or arrays that are to be read or written. This name is used by namelist-directed I/O statements instead of an input/output list. The group name must be unique, and identifies a list whose items can be read or written.

A group of variables can be defined through several NAMELIST statements with the same group name. Together, these definitions are taken as defining one NAMELIST group.

Namelist Items

The namelist items can be of any data type. The items in the namelist can be variables or arrays, and can appear in more than one namelist. Only the items specified in the namelist can be read or written in namelist-directed I/O, but it is not necessary to specify data in the input record for every item of the namelist.

The order of the items in the namelist controls the order in which the values are written in namelist-directed output. The items in the input record can be in any order.

Restrictions

Input data can assign values to the elements of arrays or to substrings of strings that appear in a namelist.

The following constructs cannot appear in a NAMELIST statement:

Example

Example: The NAMELIST statement:


       CHARACTER*16 SAMPLE 
       LOGICAL*4 NEW 
       REAL*4 DELTA 
       NAMELIST /CASE/ SAMPLE, NEW, DELTA 

In this example, the group CASE has three variables: SAMPLE, NEW, and DELTA.

OPEN

The OPEN statement can connect an existing external file to a unit, create a file and connect it to a unit, or change some specifiers of the connection.

OPEN ([UNIT=] u, slist)

Parameter 

Description 

UNIT

Unit number 

slist

The specifiers list slist can include one or more of the following

  • FILE = fin or alternativly NAME = fin

  • ACCESS = acc

  • BLANK = blnk

  • ERR = s

  • FORM = fm

  • IOSTAT = ios

  • RECL = rl or alternativly RECORDSIZE = rl

  • STATUS = sta or alternativly TYPE = sta

  • FILEOPT = fopt @

  • READONLY @

  • ACTION = act @

Description

The OPEN statement determines the type of file named, whether the connection specified is legal for the file type (for instance, DIRECT access is illegal for tape and tty devices), and allocates buffers for the connection if the file is on tape or if the subparameter FILEOPT= 'BUFFER= n' is specified. Existing files are never truncated on opening.


Note -

For tape I/O, use the TOPEN() routines.


The following table summarizes the OPEN specifiers:

Table 4-3 OPEN Specifiers Summary

Form: SPECIFIER = Variable 

SPECIFIER 

Value of Variable  

Data Type of Variable 

ACCESS

'APPEND' 'DIRECT' 'SEQUENTIAL'

CHARACTER

ACTION

'READ' 'WRITE' 'READWRITE'

CHARACTER

BLANK

'NULL'

'ZERO'

CHARACTER

ERR

Statement number  

INTEGER

FORM

'FORMATTED' 'UNFORMATTED' 'PRINT'

CHARACTER

FILE *

Filename or '*'

CHARACTER

FILEOPT

'NOPAT' 'BUFFER=n' 'EOF'

CHARACTER

IOSTAT

Error number 

INTEGER

READONLY

RECL

Record length 

INTEGER

STATUS

'OLD' 'NEW' 'UNKNOWN' 'SCRATCH'

CHARACTER

The keywords can be specified in any order.

OPEN Specifier Keywords

The following provides a detailed list of the OPEN specifier keywords:

[UNIT=] u

FILE=fin

If you open a unit that is already open without specifying a file name (or with the previous file name), FORTRAN thinks you are reopening the file to change parameters. The file position is not changed. The only parameters you are allowed to change are BLANK (NULL or ZERO) and FORM (FORMATTED or PRINT). To change any other parameters, you must close, then reopen the file.

If you open a unit that is already open, but you specify a different file name, it is as if you closed with the old file name before the open.

If you open a file that is already open, but you specify a different unit, that is an error. This error is not detected by the ERR= option, however, and the program does not terminate abnormally.

If a file is opened with STATUS='SCRATCH', a temporary file is created and opened. See STATUS=sta.

ACCESS=acc

FORM=fm

RECL=rl

ERR=s

IOSTAT=ios

BLANK=blnk

STATUS=sta

FILEOPT=fopt @

READONLY @

ACTION=act

Examples

Here are six examples.

Example 1: Open a file and connect it to unit 8--either of the following forms of the OPEN statement opens the file, projectA/data.test, and connects it to FORTRAN unit 8:


       OPEN(UNIT=8, FILE='projectA/data.test') 
       OPEN(8, FILE='projectA/data.test') 

In the above example, these properties are established by default: sequential access, formatted file, and (unwisely) no allowance for error during file open.

Example 2: Explicitly specify properties:


       OPEN(UNIT=8, FILE='projectA/data.test', &        ACCESS='SEQUENTIAL', FORM='FORMATTED')

Example 3: Either of these opens file, fort.8, and connects it to unit 8:


       OPEN(UNIT=8) 
       OPEN(8)

In the above example, you get sequential access, formatted file, and no allowance for error during file open. If the file, fort.8 does not exist before execution, it is created. The file remains after termination.

Example 4: Allowing for open errors:


       OPEN(UNIT=8, FILE='projectA/data.test', ERR=99)

The above statement branches to 99 if an error occurs during OPEN.

Example 5: Allowing for variable-length records;


       OPEN(1, ACCESS='DIRECT', recl=1)

See "Direct Access I/O" for more information about variable-length records.

Example 6: Scratch file:


       OPEN(1, STATUS='SCRATCH')

This statement opens a temporary file with a name, such as tmp.FAAAa003zU. The file is usually in the current working directory, or in TMPDIR if that environment variable is set.

OPTIONS

The OPTIONS @ statement overrides compiler command-line options.

OPTIONS /qualifier [/qualifier ]

Description

The following table shows the OPTIONS statement qualifiers:

Table 4-4 OPTIONS Statement Qualifiers

Qualifier  

Action Taken  

/[NO]G_FLOATING

None (not implemented)  

/[NO]I4

Enables/Disables the -i2 option

/[NO]F77

None (not implemented)  

/CHECK=ALL

Enables the -C option

/CHECK=[NO]OVERFLOW

None (not implemented)  

/CHECK=[NO]BOUNDS

Disables/Enables the -C option

/CHECK=[NO]UNDERFLOW

None (not implemented)  

/CHECK=NONE

Disables the -C option

/NOCHECK

Disables the -C option

/[NO]EXTEND_SOURCE

Disables/enables the -e option

Restrictions

The OPTIONS statement must be the first statement in a program unit; it must be before the BLOCK DATA, FUNCTION, PROGRAM, and SUBROUTINE statements.

Options set by the OPTIONS statement override those of the command line.

Options set by the OPTIONS statement endure for that program unit only.

A qualifier can be abbreviated to four or more characters.

Uppercase or lowercase is not significant.

Example

For the following source, integer variables declared with no explicit size occupy 4 bytes rather than 2, with or without the -i2 option on the command line. This rule does not change the size of integer constants, only variables.


       OPTIONS /I4 
       PROGRAM FFT 
       ... 
       END 

By way of contrast, if you use /NOI4, then all integer variables declared with no explicit size occupy 2 bytes rather than 4, with or without the -i2 option on the command line. However, integer constants occupy 2 bytes with -i2, and 4 bytes otherwise.

PARAMETER

The PARAMETER statement assigns a symbolic name to a constant.

PARAMETER (p=e [, p=e] )

Parameter 

Description 

p

Symbolic name  

e

Constant expression 

An alternate syntax is allowed, if the -xl flag is set: @

PARAMETER p=e [, p=e]

In this alternate form, the type of the constant expression determines the type of the name; no conversion is done.

Description

e can be of any type and the type of symbolic name and the corresponding expression must match.

A symbolic name can be used to represent the real part, imaginary part, or both parts of a complex constant.

A constant expression is made up of explicit constants and parameters and the FORTRAN operators. See "Constant Expressions" for more information.

No structured records or record fields are allowed in a constant expression.

Exponentiation to a floating-point power is not allowed, and a warning is issued.

If the type of the data expression does not match the type of the symbolic name, then the type of the name must be specified by a type statement or IMPLICIT statement prior to its first appearance in a PARAMETER statement, otherwise conversion will be performed.

If a CHARACTER statement explicitly specifies the length for a symbolic name, then the constant in the PARAMETER statement can be no longer than that length. Longer constants are truncated, and a warning is issued. The CHARACTER statement must appear before the PARAMETER statement.

If a CHARACTER statement uses *(*) to specify the length for a symbolic name, then the data in the PARAMETER statement are used to determine the length of the symbolic constant. The CHARACTER statement must appear before the PARAMETER statement.

Any symbolic name of a constant that appears in an expression e must have been defined previously in the same or a different PARAMETER statement in the same program unit.

Restrictions

A symbolic constant must not be defined more than once in a program unit.

If a symbolic name appears in a PARAMETER statement, then it cannot represent anything else in that program unit.

A symbolic name cannot be used in a constant format specification, but it can be used in a variable format specification.

If you pass a parameter as an argument, and the subprogram tries to change it, you may get a runtime error.

Examples

Example 1: Some real, character, and logical parameters:


       CHARACTER HEADING*10 
       LOGICAL T 
       PARAMETER (EPSILON=1.0E-6, PI=3.141593, 
&                 HEADING=' IO Error #', 
&                 T=.TRUE.) 
       ... 

Example 2: Let the compiler count the characters:


       CHARACTER HEADING*(*) 
       PARAMETER (HEADING='I/O Error Number') 
       ... 

Example 3: The alternate syntax, if the -xl compilation flag is specified:


       PARAMETER FLAG1 = .TRUE. 

The above statement is treated as:


       LOGICAL FLAG1 
       PARAMETER (FLAG1 = .TRUE.)

An ambiguous statement that could be interpreted as either a PARAMETER statement or an assignment statement is always taken to be the former, as long as either the -xl or -xld option is specified.

Example: An ambiguous statement:


       PARAMETER S = .TRUE.

With -xl, the above statement is a PARAMETER statement about the variable S.


       PARAMETER S = .TRUE. 

It is not an assignment statement about the variable PARAMETERS.


       PARAMETERS = .TRUE. 

PAUSE

The PAUSE statement suspends execution, and waits for you to type: go.

PAUSE [str]

Parameter 

Description 

str

String of not more than 5 digits or a character constant  

Description

The PAUSE statement suspends program execution temporarily, and waits for acknowledgment. On acknowledgment, execution continues.

If the argument string is present, it is displayed on the screen (written to stdout), followed by the following message:


       PAUSE. To resume execution, type: go 
Any other input will terminate the program. 

After you type: go, execution continues as if a CONTINUE statement is executed. See this example:


demo% cat p.f 
       PRINT *, "Start" 
       PAUSE 1 
       PRINT *, "Ok" 
       END 
demo% f77 p.f -silent
demo% a.out 
Start 
PAUSE: 1 
To resume execution, type: go 
Any other input will terminate the program. 
go 
Execution resumed after PAUSE. 
Ok 
demo%

If stdin is not a tty I/O device, PAUSE displays a message like this:


PAUSE: To resume execution, type: kill -15 pid 

where pid is the process ID.

Example: stdin not a tty I/O device:


demo% a.out < mydatafile 
PAUSE: To resume execution, type: kill -15 20537 
demo%

For the above example, type the following command line at a shell prompt in some other window. The window displaying the message cannot accept command input.


demo% kill -15 20537 

POINTER

The POINTER @ statement establishes pairs of variables and pointers.

POINTER (p1, v1) [, (p2, v2) ]

Parameter 

Description 

v1, v2

Pointer-based variables 

p1, p2

Corresponding pointers 

Description

Each pointer contains the address of its paired variable.

A pointer-based variable is a variable paired with a pointer in a POINTER statement. A pointer-based variable is usually called just a based variable. The pointer is the integer variable that contains the address.

The use of pointers is described in "Pointers ".

Examples

Example 1: A simple POINTER statement:


       POINTER (P, V) 

Here, V is a pointer-based variable, and P is its associated pointer.

Example 2: Using the LOC() function to get an address:


       * ptr1.f: Assign an address via LOC() 
       POINTER (P, V) 
       CHARACTER A*12, V*12 
       DATA A / 'ABCDEFGHIJKL' / 
       P = LOC(A) 
       PRINT *, V(5:5) 
       END 

In the above example, the CHARACTER statement allocates 12 bytes of storage for A, but no storage for V; it merely specifies the type of V because V is a pointer-based variable. You then assign the address of A to P, so now any use of V refers to A by the pointer P. The program prints an E.

Example 3: Memory allocation for pointers, by MALLOC


       POINTER (P1, X), (P2, Y), (P3, Z) 
       ... 
       P1 = MALLOC (36) 
       ... 
       CALL FREE (P1) 
       ... 

:

In the above example, you get 36 bytes of memory from MALLOC() and then, after some other instructions, probably using that chunk of memory, tell FREE() to return those same 36 bytes to the memory manager.

Example 4: Get the area of memory and its address


       POINTER (P, V) 
       CHARACTER V*12, Z*1 
       P = MALLOC(12) 
       ... 
       END 

:

In the above example, you obtain 12 bytes of memory from the function MALLOC() and assign the address of that block of memory to the pointer P.

Example 5: Dynamic allocation of arrays:


       PROGRAM UsePointers 
       REAL X 
       POINTER (P, X) 
       ... 
       READ (*,*) Nsize 	! Get the size. 
       P = MALLOC(Nsize)	! Allocate the memory. 
       ... 
       CALL CALC (X, Nsize) 
       ... 
       END 
       SUBROUTINE CALC (A, N) 
       REAL A(N) 
                   ! Use the array of whatever size. 
       RETURN 
       END 

This is a slightly more realistic example. The size might well be some large number, say, 10,000. Once that's allocated, the subroutines perform their tasks, not knowing that the array was dynamically allocated.

Example 6: One way to use pointers to make a linked list in f77:


demo% cat Linked.f
              STRUCTURE /NodeType/
                     INTEGER recnum
                     CHARACTER*3 label
                     INTEGER next
              END STRUCTURE
              RECORD /NodeType/ r, b
              POINTER (pr,r), (pb,b)
              pb = malloc(12) Create the base record, b.
              pr = pb                     Make pr point to b.
              NodeNum = 1 
              DO WHILE (NodeNum .LE. 4) Initialize/create records
                     IF (NodeNum .NE. 1) pr = r.next
                     CALL struct_creat(pr,NodeNum)
                     NodeNum = NodeNum + 1
              END DO
              r.next = 0
              pr = pb                     Show all records.
              DO WHILE (pr .NE. 0)
                     PRINT *, r.recnum, " ", r.label
                     pr = r.next
              END DO
              END
              SUBROUTINE struct_creat(pr,Num)
              STRUCTURE /NodeType/
                     INTEGER recnum
                     CHARACTER*3 label
                     INTEGER next
              END STRUCTURE

              RECORD /NodeType/ r
              POINTER (pr,r), (pb,b)
              CHARACTER v*3(4)/'aaa', 'bbb', 'ccc', 'ddd'/

              r.recnum = Num                     Initialize current record.
              r.label = v(Num)
              pb = malloc(12)                  Create next record.
              r.next = pb
              RETURN
              END


demo% f77 -silent Linked.f
"Linked.f", line 6: Warning: local variable "b" never used
"Linked.f", line 31: Warning: local variable "b" never used
demo% a.out
       1 aaa
       2 bbb
       3 ccc
       4 ddd
demo% 

Remember:

PRINT

The PRINT statement writes from a list to stdout.

PRINT f [, iolist]

PRINT grname

Parameter 

Description 

f

Format identifier 

iolist

List of variables, substrings, arrays, and records 

grname

Name of the namelist group 

Description

The PRINT statement accepts the following arguments.

Format Identifier

f is a format identifier and can be:

Output List

iolist can be empty or can contain output items or implied DO lists. The output items must be one of the following:

A simple unsubscripted array name specifies all of the elements of the array in memory storage order, with the leftmost subscript increasing more rapidly.

Implied DO lists are described on "Implied DO Lists".

Namelist-Directed PRINT

The second form of the PRINT statement is used to print the items of the specified namelist group. Here, grname is the name of a group previously defined by a NAMELIST statement.

Execution proceeds as follows:

  1. The format, if specified, is established.

  2. If the output list is not empty, data is transferred from the list to standard output.

    If a format is specified, data is edited accordingly.

  3. In the second form of the PRINT statement, data is transferred from the items of the specified namelist group to standard output.

Restrictions

Output from an exception handler is unpredictable. If you make your own exception handler, do not do any FORTRAN output from it. If you must do some, then call abort right after the output. Doing so reduces the relative risk of a program freeze. FORTRAN I/O from an exception handler amounts to recursive I/O. See the next point.

Recursive I/O does not work reliably. If you list a function in an I/O list, and if that function does I/O, then during runtime, the execution may freeze, or some other unpredictable problem may occur. This risk exists independent of parallelization.

Example: Recursive I/O fails intermittently:


       PRINT *, x, f(x)                 Not allowed because f() does I/O.
       END
       FUNCTION F(X)
       PRINT *, X
       RETURN
       END

Examples

Example 1: Formatted scalars:


       CHARACTER TEXT*16 
       PRINT 1, NODE, TEXT 
1     FORMAT (I2, A16) 

Example 2: List-directed array:


       PRINT *, I, J, (VECTOR(I), I = 1, 5) 

Example 3: Formatted array:


       INTEGER VECTOR(10) 
       PRINT '(12 I2)', I, J, VECTOR 

Example 4: Namelist:


       CHARACTER LABEL*16 
       REAL QUANTITY 
       INTEGER NODE 
       NAMELIST /SUMMARY/ LABEL, QUANTITY, NODE 
       PRINT SUMMARY 

PROGRAM

The PROGRAM statement identifies the program unit as a main program.

PROGRAM pgm

Parameter 

Description 

pgm

Symbolic name of the main program 

Description

For the loader, the main program is always named MAIN. The PROGRAM statement serves only the person who reads the program.

Restrictions

The PROGRAM statement can appear only as the first statement of the main program.

The name of the program cannot be:

The name of the program can be the same as a local name in the main program.@ The FORTRAN 77 Standard does not allow this practice.

Example

Example: A PROGRAM statement:


       PROGRAM US_ECONOMY 
       NVARS = 2 
       NEQS = 2 
       ... 

READ

The READ statement reads data from a file or the keyboard to items in the list.


Note -

Use the TOPEN() routines to read from tape devices. See the Fortran Library Reference Manual.


READ([UNIT=] u [, [FMT=]f] [, IOSTAT=ios] [, REC=rn] [, END=s] [, ERR=s])iolist

READ f [, iolist]

READ([UNIT=] u, [NML=] grname [, IOSTAT=ios] [, END=s] [, ERR=s])

READ grname

Parameter 

Description 

u

Unit identifier of the unit connected to the file 

f

Format identifier 

ios

I/O status specifier 

rn

Record number to be read 

s

Statement label for end of file processing  

iolist

List of variables  

grname

Name of a namelist group 

An alternate to the UNIT=u, REC=rn form is as follows: @

READ( u 'rn ... ) iolist

The options can be specified in any order.

Description

The READ statement accepts the following arguments.

Unit Identifier

u is either an external unit identifier or an internal file identifier.

An external unit identifier must be one of these:

If the optional characters UNIT= are omitted from the unit specifier, then u must be the first item in the list of specifiers.

Format Identifier

f is a format identifier and can be:

See "Runtime Formats " for details on formats evaluated at runtime.

If the optional characters, FMT=, are omitted from the format specifier, then f must appear as the second argument for a formatted read; otherwise, it must not appear at all.

Unformatted data transfer from internal files and terminal files is not allowed, hence, f must be present for such files.

List-directed data transfer from direct-access and internal files is allowed; hence, f can be an asterisk for such files. @

If a file is connected for formatted I/O, unformatted data transfer is not allowed, and vice versa.

I/O Status Specifier

ios must be an integer variable or an integer array element.

Record Number

rn must be a positive integer expression, and can be used for direct-access files only. rn can be specified for internal files. @

End-of-File Specifier

s must be the label of an executable statement in the same program unit in which the READ statement occurs.

The END=s and REC=rn specifiers can be present in the same READ statement. @

Error Specifier

s must be the label of an executable statement in the same program unit in which the READ statement occurs.

Input List

iolist can be empty or can contain input items or implied DO lists. The input items can be any of the following:

A simple unsubscripted array name specifies all of the elements of the array in memory storage order, with the leftmost subscript increasing more rapidly.

Implied DO lists are described on "Implied DO Lists".

Namelist-Directed READ

The third and fourth forms of the READ statement are used to read the items of the specified namelist group, and grname is the name of the group of variables previously defined in a NAMELIST statement.

Execution

Execution proceeds as follows:

  1. The file associated with the specified unit is determined.

    The format, if specified, is established. The file is positioned appropriately prior to the data transfer.

  2. If the input list is not empty, data is transferred from the file to the corresponding items in the list.

    The items are processed in order as long as the input list is not exhausted. The next specified item is determined and the value read is transmitted to it. Data editing in formatted READ is done according to the specified format.

  3. In the third and fourth forms of namelist-directed READ, the items of the specified namelist group are processed according to the rules of namelist-directed input.

  4. The file is repositioned appropriately after data transfer.

  5. If ios is specified and no error occurred, it is set to zero.

    ios is set to a positive value, if an error or end of file was encountered.

  6. If s is specified and end of file was encountered, control is transferred to s.

  7. If s is specified and an error occurs, control is transferred to s.

There are two forms of READ:

READ f [, iolist]

READ([NML= ] grname)

The above two forms operate the same way as the others, except that reading from the keyboard is implied.

Execution has the following differences:

If u specifies an external unit that is not connected to a file, an implicit OPEN operation is performed equivalent to opening the file with the options in the following example:


       OPEN(u,
FILE='FORT.u', STATUS='OLD', ACCESS='SEQUENTIAL', 
&              FORM=fmt
)

Note also:

Examples

Example 1: Formatted read, trap I/O errors, EOF, and I/O status:


       READ( 1, 2, ERR=8, END=9, IOSTAT=N ) X, Y 
       ... 
8     WRITE( *, * ) 'I/O error # ', N, ', on 1' 
       STOP 
9     WRITE( *, * ) 'EoF on 1' 
       RETURN 
       END 

Example 2: Direct, unformatted read, trap I/O errors, and I/O status:


       READ( 1, REC=3, IOSTAT=N, ERR=8 ) V 
       ... 
4     CONTINUE 
       RETURN 
8     WRITE( *, * ) 'I/O error # ', N, ', on 1' 
       END 

Example 3: List-directed read from keyboard:


       
READ(*,*) A, V
or
       READ*, A, V

Example 4: Formatted read from an internal file:


       CHARACTER CA*16 / 'abcdefghijklmnop' /, L*8, R*8
        READ( CA, 1 ) L, R
1     FORMAT( 2 A8 )

Example 5: Read an entire array:


       DIMENSION V(5) 
       READ( 3, '(5F4.1)') V 

Example 6: Namelist-directed read:


       CHARACTER SAMPLE*16 
       LOGICAL NEW*4 
       REAL DELTA*4 
       NAMELIST /G/SAMPLE,NEW,DELTA 
       ... 
       READ(1, G) 
            or 
       READ(UNIT=1, NML=G) 
            or 
       READ(1, NML=G)

REAL

The REAL statement specifies the type of a symbolic constant, variable, array, function, or dummy function to be real, and optionally specifies array dimensions and size, and initializes with values.

REAL [*len[,]] v[*len[/c/]] [, v[*len[/c/]] ...

Parameter 

Description 

v

Name of a variable, symbolic constant, array, array declarator, function, or dummy function 

len

Either 4, 8, or 16 (SPARC only), the length in bytes of the symbolic constant, variable, array element, or function

c

List of constants for the immediately preceding name  

Description

Following are descriptions for REAL, REAL*4, REAL*8, and REAL*16.

REAL

For a declaration such as REAL W, the variable W is usually a REAL*4 element in memory, interpreted as a real number. Specifying the size is nonstandard. @

The default size, for a declaration such as REAL H, can be altered by compiling with any of the options -dbl, -r8, or -xtypemap. See the discussion in Chapter 2 for details.

REAL*4 @

For a declaration such as REAL*4 W, the variable W is always a REAL*4 element in memory, interpreted as a single-width real number.

REAL*8 @

For a declaration such as REAL*8 W, the variable W is always a REAL*8 element in memory, interpreted as a double-width real number.

REAL*16 @

(SPARC only) For a declaration such as REAL*16 W, the variable W is always an element of type REAL*16 in memory, interpreted as a quadruple-width real.

Examples

Example 1: Simple real variables--these declarations are all equivalent:


       REAL U, V(9)
       REAL*4 U, V(9)
       REAL U*4, V(9)*4

Example 2: Initialize variables (REAL*16 is SPARC only):


       REAL U/ 1.0 /, V/ 4.3 /, D*8/ 1.0 /, Q*16/ 4.5 / 

Example 3: Specify dimensions for some real arrays:


       REAL A(10,100), V(10)
       REAL X*4(10), Y(10)*4

Example 4: Initialize some arrays:


       REAL A(10,100) / 1000 * 0.0 /, B(2,2) /1.0, 2.0, 3.0, 4.0/ 

Example 5: Double and quadruple precision (REAL*16 is SPARC only):


       REAL*8  R
       REAL*16 Q
       DOUBLE PRECISION D

In the above example, D and R are both double precision; Q is quadruple precision.

RECORD

The RECORD @ statement defines variables to have a specified structure, or arrays to be arrays of variables with such structures.

RECORD /struct-name/ record-list [,/struct-name/ record-list]...

Parameter 

Description 

struct_name

Name of a previously declared structure  

record_list

List of variables, arrays, or array declarators 

Description

A structure is a template for a record. The name of the structure is included in the STRUCTURE statement, and once a structure is thus defined and named, it can be used in a RECORD statement.

The record is a generalization of the variable or array: where a variable or array has a type, the record has a structure. Where all the elements of an array must be of the same type, the fields of a record can be of different types.

The RECORD line is part of an inherently multiline group of statements, and neither the RECORD line nor the END RECORD line has any indication of continuation. Do not put a nonblank in column six, nor an & in column one.

Structures, fields, and records are discussed in "Structures".

Restrictions

Example

Example 1: Declare some items to be records of a specified structure:


       STRUCTURE /PRODUCT/ 
             INTEGER*4 ID 
             CHARACTER*16 NAME 
             CHARACTER*8 MODEL 
             REAL*4 COST 
             REAL*4 PRICE 
       END STRUCTURE 
       RECORD /PRODUCT/ CURRENT, PRIOR, NEXT, LINE(10)
       ...

Each of the three variables CURRENT, PRIOR, and NEXT is a record which has the PRODUCT structure, and LINE is an array of 10 such records.

Example 2: Define some fields of records, then use them:


       STRUCTURE /PRODUCT/
              INTEGER*4    ID
              CHARACTER*16 NAME
              CHARACTER*8  MODEL
              REAL*4       COST
              REAL*4       PRICE
       END STRUCTURE
       RECORD /PRODUCT/  CURRENT, PRIOR, NEXT, LINE(10)
       CURRENT.ID = 82
       PRIOR.NAME = "CacheBoard"
       NEXT.PRICE = 1000.00
       LINE(2).MODEL = "96K"
       PRINT 1, CURRENT.ID, PRIOR.NAME, NEXT.PRICE,LINE(2).MODEL
1      FORMAT(1X I5/1X A16/1X F8.2/1X A8)
       END

The above program produces the following output:


82
CacheBoard
1000.00
96K

RETURN

A RETURN statement returns control to the calling program unit.

RETURN [e]

Parameter 

Description 

e

Expression of type INTEGER or REAL

Description

Execution of a RETURN statement terminates the reference of a function or subroutine.

Execution of an END statement in a function or a subroutine is equivalent to the execution of a RETURN statement. @

The expression e is evaluated and converted to integer, if required. e defines the ordinal number of the alternate return label to be used. Alternate return labels are specified as asterisks (or ampersands) @ in the SUBROUTINE statement.

If e is not specified, or the value of e is less than one or greater than the number of asterisks or ampersands in the SUBROUTINE statement that contains the RETURN statement, control is returned normally to the statement following the CALL statement that invoked the subroutine.

If the value of e is between one and the number of asterisks (or ampersands) in the SUBROUTINE statement, control is returned to the statement identified by the eth alternate. A RETURN statement can appear only in a function subprogram or subroutine.

Examples

Example 1: Standard return:


       CHARACTER*25 TEXT 
       TEXT = "Some kind of minor catastrophe"
       ... 
       CALL OOPS ( TEXT ) 
       STOP 
       END
       SUBROUTINE OOPS ( S ) 
       CHARACTER S* 32 
       WRITE (*,*) S 
       RETURN 
       END 

Example 2: Alternate return:


       CALL RANK ( N, *8, *9 ) 
       WRITE (*,*) 'OK - Normal Return' 
       STOP 
8     WRITE (*,*) 'Minor - 1st alternate return' 
       STOP 
9     WRITE (*,*) 'Major - 2nd alternate return' 
       END 
       SUBROUTINE RANK (N, *,*) 
       IF ( N .EQ. 0 ) RETURN 
       IF ( N .EQ. 1 ) RETURN 1 
       RETURN 2 
       END 

REWIND

The REWIND statement positions the file associated with the specified unit to its initial point.


Note -

Use the TOPEN() routines to rewind tape devices. See the Fortran Library Reference Manual for details.


REWIND u

REWIND ([UNIT=] u [, IOSTAT=ios] [, ERR= s])

Parameter 

Description 

u

Unit identifier of an external unit connected to the file u must be connected for sequential access, or append access.

ios

I/O specifier, an integer variable or an integer array element  

s

Error specifier: s must be the label of an executable statement in the same program in which this REWIND statement occurs. The program control is transferred to this label in case of an error during the execution of the REWIND statement.

Description

The options can be specified in any order.

Rewinding a unit not associated with any file has no effect. Likewise, REWIND in a terminal file has no effect either.

Using a REWIND statement on a direct-access file is not defined in the FORTRAN 77 Standard, and is unpredictable.

Examples

Example 1: Simple form of unit specifier:


       ENDFILE 3 
       REWIND 3 
       READ (3,'(I2)') I 
       REWIND 3 
       READ (3,'(I2)')I 

Example 2: REWIND with the UNIT=u form of unit specifier and error trap:


       INTEGER  CODE
       ...
       REWIND (UNIT = 3) 
       REWIND (UNIT = 3, IOSTAT = CODE, ERR = 100) 
       ... 
100       WRITE (*,*) 'error in rewinding'
       STOP 

SAVE

The SAVE statement preserves items in a subprogram after the RETURN or END statements are executed, preventing them from becoming undefined.

SAVE [ v [, v ] ]

Parameter 

Description 

v

Name of an array, variable, or common block (enclosed in slashes), occurring in a subprogram  

Description

SAVE variables are placed in an internal static area. All common blocks are already preserved because they have been allocated to a static area. Therefore, common block names specified in SAVE statements are allowed but ignored.

A SAVE statement is optional in the main program and has no effect.

A SAVE with no list preserves all local variables and arrays in the routine.

Local variables and arrays are already static by default, predisposing the need for SAVE. However, using SAVE can ensure portability, especially with routines that leave a subprogram by some way other than a RETURN.

Restrictions

The following constructs must not appear in a SAVE statement:

Example

Example: A SAVE statement:


       SUBROUTINE FFA(N) 
       DIMENSION A(1000,1000), V(1000) 
       SAVE A 
       ... 
       RETURN 
       END 

Statement Function

A statement function statement is a function-like declaration, made in a single statement.

fun ([d[, d]]) = e

Parameter 

Description 

fun

Name of statement function being defined 

d

Statement function dummy argument  

e

Expression. e can be any of the types arithmetic, logical, or character.

Description

If a statement function is referenced, the defined calculations are inserted.

Example: The following statement is a statement function:


       ROOT( A, B, C ) = (-B + SQRT(B**2-4.0*A*C))/(2.0*A) 

The statement function argument list indicates the order, number, and type of arguments for the statement function.

A statement function is referenced by using its name, along with its arguments, as an operand in an expression.

Execution proceeds as follows:

  1. If they are expressions, actual arguments are evaluated.

  2. Actual arguments are associated with corresponding dummy arguments.

  3. The expression e, the body of a statement function, is evaluated.

  4. If the type of the above result is different from the type of the function name, then the result is converted.

  5. Return the value.

The resulting value is thus available to the expression that referenced the function.

Restrictions

Note these restrictions:

Examples

Example 1: Arithmetic statement function:


       PARAMETER ( PI=3.14159 ) 
       REAL RADIUS, VOLUME 
       SPHERE ( R ) = 4.0 * PI * (R**3) / 3.0 
       READ *, RADIUS 
       VOLUME = SPHERE( RADIUS ) 
       ... 

Example 2: Logical statement function:


       LOGICAL OKFILE 
       INTEGER STATUS 
       OKFILE ( I ) = I .LT. 1 
       READ( *, *, IOSTAT=STATUS ) X, Y 
       IF ( OK FILE(STATUS) ) CALL CALC ( X, Y, A ) 
       ... 

Example 3: Character statement function:


       CHARACTER FIRST*1, STR*16, S*1
       FIRST(S) = S(1:1) 
       READ( *, * ) STR 
       IF ( FIRST(STR) .LT. " " ) CALL CONTROL ( S, A ) 
       ... 

STATIC

The STATIC @ statement ensures that the specified items are stored in static memory.

STATIC list

Parameter 

Description 

list

List of variables and arrays 

Description

All local variables and arrays are classified static by default: there is exactly one copy of each datum, and its value is retained between calls. You can also explicitly define variables as static or automatic in a STATIC or AUTOMATIC statement, or in any type statement or IMPLICIT statement.

However, you can still use STATIC to ensure portability, especially with routines that leave a subprogram by some way other than a RETURN.

Also note that:

Example


       STATIC A, B, C 
       REAL P, D, Q 
       STATIC P, D, Q 
       IMPLICIT STATIC (X-Z) 

STOP

The STOP statement terminates execution of the program.

STOP [str]

Parameter 

Description 

str

String of no more that 5 digits or a character constant 

Description

The argument str is displayed when the program stops.

If str is not specified, no message is displayed.

Examples

Example 1: Integer:


       stop 9 

The above statement displays:


       STOP: 9 

Example 2: Character:


       stop 'error' 

The above statement displays:


       STOP: error

STRUCTURE

The STRUCTURE @ statement organizes data into structures.

STRUCTURE [/structure-name/] [field-list]

      field-declaration

     field-declaration

    . . .

END STRUCTURE

Each field declaration can be one of the following:

Description

A STRUCTURE statement defines a form for a record by specifying the name, type, size, and order of the fields that constitute the record. Optionally, it can specify the initial values.

A structure is a template for a record. The name of the structure is included in the STRUCTURE statement, and once a structure is thus defined and named, it can be used in a RECORD statement.

The record is a generalization of the variable or array--where a variable or array has a type, the record has a structure. Where all the elements of an array must be of the same type, the fields of a record can be of different types.

Structures, fields, and records are described in "Structures".

Restrictions

The name is enclosed in slashes and is optional in nested structures only.

If slashes are present, a name must be present.

You can specify the field-list within nested structures only.

There must be at least one field-declaration.

Each structure-name must be unique among structures, although you can use structure names for fields in other structures or as variable names.

The only statements allowed between the STRUCTURE statement and the END STRUCTURE statement are field-declaration statements and PARAMETER statements. A PARAMETER statement inside a structure declaration block is equivalent to one outside.

Restrictions for Fields

Fields that are type declarations use the identical syntax of normal FORTRAN type statements, and all f77 types are allowed, subject to the following rules and restrictions:

In a structure declaration, the offset of field n is the offset of the preceding field, plus the length of the preceding field, possibly corrected for any adjustments made to maintain alignment.

You can initialize a field that is a variable, array, substring, substructure, or union.

Examples

Example 1: A structure of five fields:


       STRUCTURE /PRODUCT/ 
              INTEGER*4 ID / 99 / 
              CHARACTER*16 NAME 
              CHARACTER*8 MODEL / 'Z' / 
              REAL*4 COST 
              REAL*4 PRICE 
       END STRUCTURE 
       RECORD /PRODUCT/ CURRENT, PRIOR, NEXT, LINE(10) 

In the above example, a structure named PRODUCT is defined to consist of the fields ID, NAME, MODEL, COST, and PRICE. Each of the three variables, CURRENT, PRIOR, and NEXT, is a record which has the PRODUCT structure, and LINE is an array of 10 such records. Every such record has its ID initially set to 99, and its MODEL initially set to Z.

Example 2: A structure of two fields:


       STRUCTURE /VARLENSTR/ 
              INTEGER*4 NBYTES 
              CHARACTER A*25 
       END STRUCTURE 
       RECORD /VARLENSTR/ VLS 
       VLS.NBYTES = 0 

SUBROUTINE

The SUBROUTINE statement identifies a named program unit as a subroutine, and specifies arguments for it.

SUBROUTINE sub [([ d[, d]])]

Parameter 

Description 

sub

Name of subroutine subprogram  

d

Variable name, array name, record name, or dummy procedure name, an asterisk, or an ampersand  

Description

A subroutine subprogram must have a SUBROUTINE statement as the first statement. A subroutine can have any other statements, except a BLOCK DATA, FUNCTION, PROGRAM, or another SUBROUTINE statement.

sub is the name of a subroutine and is a global name, and must not be the same as any other global name such as a common block name or a function name. Nor can it be the same as any local name in the same subroutine.

d is the dummy argument, and multiple dummy arguments are separated by commas. d can be one of the following:

The dummy arguments are local to the subroutine and must not appear in any of the following statements, except as a common block name:

The actual arguments in the CALL statement that references a subroutine must agree with the corresponding formal arguments in the SUBROUTINE statement, in order, number, and type. An asterisk (or an ampersand) in the formal argument list denotes an alternate return label. A RETURN statement in this procedure can specify the ordinal number of the alternate return to be taken.

Examples

Example 1: A variable and array as parameters:


       SUBROUTINE SHR ( A, B ) 
       CHARACTER A*8 
       REAL B(10,10) 
       ...
       RETURN 
       END 

Example 2: Standard alternate returns:


       PROGRAM TESTALT 
       CALL RANK ( N, *8, *9 ) 
       WRITE (*,*) 'OK - Normal Return [n=0]' 
       STOP 
8     WRITE (*,*) 'Minor - 1st alternate return [n=1]' 
       STOP 
9     WRITE (*,*) 'Major - 2nd alternate return [n=2]' 
       END 
       SUBROUTINE RANK ( N, *, * ) 
       IF ( N .EQ. 0 ) RETURN 
       IF ( N .EQ. 1 ) RETURN 1
       RETURN 2 
       END

In this example, the RETURN 1 statement refers to the first alternate return label (first *). The RETURN 2 statement refers to the second alternate return label (second *) specified in the SUBROUTINE statement.

TYPE

The TYPE @ statement writes to stdout.

TYPE f [, iolist]

TYPE grname

Parameter 

Description 

f

Format identifier 

iolist

List of variables, substrings, arrays, and records 

grname

Name of the namelist group 

Description

The TYPE statement is provided for compatibility and is equivalent to:

Example

Example: Formatted and namelist output:


       INTEGER V(5) 
       REAL X(9), Y
       NAMELIST /GNAM/ X, Y
       ...
       TYPE 1, V 
1     FORMAT( 5 I3 ) 
       ...
       TYPE GNAM
       ...

The Type Statement

The type statement specifies the data type of items in the list, optionally specifies array dimensions, and initializes with values.

type v [/ clist /] [, v [/ clist /]...

Parameter 

Description 

type 

One of the following:

BYTE @

CHARACTER

CHARACTER*n (where n is greater than 0)

CHARACTER*(*)

COMPLEX

COMPLEX*8 @

COMPLEX*16 @

COMPLEX*32 @(SPARC only)

DOUBLE COMPLEX @

INTEGER

INTEGER*2 @

INTEGER*4 @

INTEGER*8 @

LOGICAL

LOGICAL*1 @

LOGICAL*2 @

LOGICAL*4 @

LOGICAL*8 @

REAL

REAL*4 @

REAL*8 @

REAL*16 @(SPARC only)

DOUBLE PRECISION

v

Variable name, array name, array declarator, symbolic name of a constant, statement function or function subprogram name 

clist

List of constants. There are more details about clist in the section on the DATA statement.

type can be preceded by either AUTOMATIC or STATIC.

Description

A type statement can be used to:

A type statement can assign initial values to variables, arrays, or record fields by specifying a list of constants (clist) as in a DATA statement. @

The general form of a type statement is:

type VariableName / constant /

or

type ArrayName / constant, /

or

type ArrayName / r*constant /

Example: Various type statements:


       CHARACTER LABEL*12 / 'Standard' /
       COMPLEX STRESSPT / ( 0.0, 1.0 ) /
       INTEGER COUNT / 99 /, Z / 1 /
       REAL PRICE / 0.0 /, COST / 0.0 /
       REAL LIST(8) / 0.0, 6*1.0, 0.0 /

When you initialize a data type, remember the following restrictions:

Restrictions

A symbolic name can appear only once in type statements in a program unit.

A type statement must precede all executable statements.

Example

Example: The type statement:


       INTEGER*2 I, J/0/ 
       REAL*4 PI/3.141592654/,ARRAY(10)/5*0.0,5*1.0/ 
       CHARACTER*10 NAME 
       CHARACTER*10 TITLE/'Heading'/ 

In the above example:

UNION and MAP

The UNION @ statement defines groups of fields that share memory at runtime.

The syntax of a UNION declaration is as follows:


UNION
       MAP
              field-declaration
              field-declaration
              ...
       MAP
              field-declaration
              field-declaration
              ...
       END 
MAP
END UNION

Description

A MAP statement defines alternate groups of fields in a union. During execution, one map at a time is associated with a shared storage location. When you reference a field in a map, the fields in any previous map become undefined, and are succeeded by the fields in the map of the newly referenced field. Also:

The UNION line is part of an inherently multiline group of statements, and neither the UNION line nor the END UNION line has any special indication of continuation. You do not put a nonblank in column six, nor an & in column one.

Each field-declaration in a map declaration can be one of the following:

Example

Declare the structure /STUDENT/ to contain either NAME, CLASS, and MAJOR, or NAME, CLASS, CREDITS, and GRAD_DATE:


       STRUCTURE /STUDENT/ 
       CHARACTER*32  NAME 
       INTEGER*2  CLASS 
       UNION 
              MAP 
                     CHARACTER*16 MAJOR 
              END MAP 
              MAP 
                     INTEGER*2  CREDITS 
                     CHARACTER*8  GRAD_DATE 
              END MAP 
       END UNION 
       END STRUCTURE 
       RECORD /STUDENT/ PERSON 

In the above example, the variable PERSON has the structure /STUDENT/, so:

VIRTUAL

The VIRTUAL @ statement is treated the same as the DIMENSION statement.

VIRTUAL a(d) [, a(d)] ...

Parameter 

Description 

a

Name of an array  

a(d)

Specifies the dimension of the array. It is a list of 1 to 7 declarators separated by commas  

Description

The VIRTUAL statement has the same form and effect as the DIMENSION statement. It is included for compatibility with older versions of FORTRAN.

Example


       VIRTUAL M(4,4), V(1000) 
       ... 
       END 

VOLATILE

The VOLATILE @ statement prevents optimization on the specified items.

VOLATILE nlist

Parameter 

Description 

nlist

List of variables, arrays, or common blocks 

Description

The VOLATILE statement prevents optimization on the items in the list. Programs relying on it are usually nonportable.

Example

Example: VOLATILE: @


       PROGRAM FFT 
       INTEGER NODE*2, NSTEPS*2 
       REAL DELTA, MAT(10,10), V(1000), X, Z 
       COMMON /INI/ NODE, DELTA, V 
       ... 
       VOLATILE V, Z, MAT, /INI/ 
       ... 
       EQUIVALENCE ( X, V ) 
       ... 

In the above example, the array V, the variable Z, and the common block /INI/ are explicitly specified as VOLATILE. The variable X is VOLATILE through an equivalence.

WRITE

The WRITE statement writes data from the list to a file.


Note -

For tape I/O, use the TOPEN() routines.


WRITE([UNIT=] u [, [FMT=] f] [, IOSTAT=ios] [, REC=rn] [, ERR=s]) iolist

WRITE([ UNIT=] u, [NML=] grname [, IOSTAT=ios] [, ERR=s])

Parameter 

Description 

u

Unit identifier of the unit connected to the file  

f

Format identifier  

ios

I/O status specifier  

rn

Record number  

s

Error specifier (statement label)  

iolist

List of variables  

grname

Name of the namelist group

The options can be specified in any order.

An alternate for the REC=rn form is allowed, as follows: @


        WRITE( u
 ' rn 
) iolist 
@

See Example 3, later on in this section.

Description

Unit Identifier

u is either an external unit identifier or an internal file identifier.

An external unit identifier must be one of the following:

If the optional characters UNIT= are omitted from the unit specifier, then u must be the first item in the list of specifiers.

Format Identifier

f is a format identifier and can be:

See "Runtime Formats " for details on formats evaluated at runtime.

If the optional characters, FMT=, are omitted from the format specifier, then f must appear as the second argument for a formatted write; otherwise, it must not appear at all.

f must not be an asterisk for direct access.

f can be an asterisk for internal files. @

If a file is connected for formatted I/O, unformatted data transfer is prohibited, and vice versa.

I/O Status Specifier

ios must be an integer variable, integer array element, or integer record field.

Record Number

rn must be a positive integer expression. This argument can appear only for direct-access files. rn can be specified for internal files. @

Error Specifier

s must be the label of an executable statement in the same program unit in which this WRITE statement occurs.

Output List

iolist can be empty, or it can contain output items or implied DO lists. The output items must be one of the following:

A simple unsubscripted array name specifies all of the elements of the array in memory storage order, with the leftmost subscript increasing more rapidly.

Implied DO lists are described in "Implied DO Lists".

If the output item is a character expression that employs the concatenation operator, the length specifiers of its operands can be an asterisk (*). This rule is nonstandard. @

If a function appears in the output list, that function must not cause an input/output statement to be executed.

Namelist-Directed WRITE

The second form of WRITE is used to output the items of the specified namelist group. Here, grname is the name of the list previously defined in a NAMELIST statement.

Execution

Execution proceeds as follows:

  1. The file associated with the specified unit is determined.

    The format, if specified, is established. The file is positioned appropriately prior to data transfer.

  2. If the output list is not empty, data is transferred from the list to the file.

    Data is edited according to the format, if specified.

  3. In the second form of namelist-directed WRITE, the data is transferred from the items of the specified namelist group according to the rules of namelist-directed output.

  4. The file is repositioned appropriately after the data transfer.

  5. If ios is specified, and no error occurs, it is set to zero; otherwise, it is set to a positive value.

  6. If s is specified and an error occurs, control is transferred to s.

Restrictions

Note these restrictions:

Comments

If u specifies an external unit that is not connected to a file, an implicit OPEN operation is performed that is equivalent to opening the file with the following options:


       OPEN(u
, FILE='FORT.u
', STATUS='UNKNOWN',       & ACCESS='SEQUENTIAL', FORM=fmt
)

The value of fmt is 'FORMATTED' if the write is formatted, and 'UNFORMATTED' otherwise.

A simple unsubscripted array name specifies all of the elements of the array in memory storage order, with the leftmost subscript increasing more rapidly.

The record number for direct-access files starts from one onwards.

Namelist-directed output is permitted on sequential access files only.

Examples

Example 1: Formatted write with trap I/O errors and I/O status:


       WRITE( 1, 2, ERR=8, IOSTAT=N ) X, Y 
       RETURN 
       ... 
8     WRITE( *, * ) 'I/O error # ', N, ', on 1' 
       STOP 
       END 

Example 2: Direct, unformatted write, trap I/O errors, and I/O status:


       ... 
       WRITE( 1, REC=3, IOSTAT=N, ERR=8 ) V 
       ... 
4     CONTINUE 
       RETURN 
8     WRITE( *, * ) 'I/O error # ', N, ', on 1' 
       END 

Example 3: Direct, alternate syntax (equivalent to above example):


       ... 
       WRITE( 1 ' 3, IOSTAT=N, ERR=8 ) V 
@
       ... 
4      CONTINUE
       RETURN
8      WRITE( *, * ) 'I/O error # ', N, ', on 1' 
       END 

@

Example 4: List-directed write to screen:


       WRITE( *, * ) A, V 
or 
       PRINT *, A, V 

Example 5: Formatted write to an internal file:


       CHARACTER CA*16, L*8 /'abcdefgh'/, R*8 /'ijklmnop'/
       WRITE( CA, 1 ) L, R
1      FORMAT( 2 A8 ) 

Example 6: Write an entire array


       DIMENSION V(5) 
       WRITE( 3, '(5F4.1)') V

:

Example 7: Namelist-directed write:.


       CHARACTER SAMPLE*16 
       LOGICAL NEW*4 
       REAL DELTA*4 
       NAMELIST /G/ SAMPLE, NEW, DELTA 
       ... 
       WRITE( 1, G ) 
or 
       WRITE( UNIT=1, NML=G ) 
or 
       WRITE( 1, NML=G )