FORTRAN Syntax

Computer Methods in Chemical Engineering

--Extracted from FORLANG.HLP by Nam Sun Wang--

List of FORTRAN Statements




ALLOCATE

Action Dynamically sizes an array previously declared with the ALLOCATABLE attribute. Syntax ALLOCATE (array([l:]u[,[l:]u ...]) [, STAT = ierr]) ... Parameter Description array Name of allocatable array ierr Integer variable that returns error status l Integer expression that sets the lower bound of the array u Integer expression that sets the upper bound of the array Remarks Allocatable arrays are dynamically allocated and deallocated at run time. Allocatable arrays may not have the NEAR attribute. If the array may be larger than 65,536 bytes, you must specify the HUGE attribute so the array elements are correctly addressed. Allocatable arrays may not appear in AUTOMATIC, COMMON, DATA, EQUIVALENCE, or STRUCTURE statements. The variable returns a value of zero if the allocation was successful, and the number of the run-time error if the allocation failed. If the ISTAT= parameter is not specified and an error occurs, the program is halted and a run-time error is generated. See Also: DEALLOCATE Example . . . INTEGER dataset[ALLOCATABLE](:,:), + results[ALLOCATABLE, HUGE](:,:,:) INTEGER reactor, level, calcs, error DATA reactor, level, calcs / 10, 50, 100 / ALLOCATE (dataset(reactor,level), + results(reactor,level,calcs), STAT = error) IF (error .NE. 0) + STOP 'Not enough storage for data; aborting...' . . .


ASSIGN (Label Assignment)

Action Assigns the value of a format or statement label to an integer variable. Syntax ASSIGN label TO variable Parameter Description label A format label or statement label, which must appear in the same program unit. variable An integer variable. Remarks If you use INTEGER*1 variables for , note that INTEGER*1 variables can only be used for the first 128 ASSIGN statements in a subprogram. Example C Assign statement label 100 to the integer variable ivar ASSIGN 100 TO ivar C Use ivar as a FORMAT statement label WRITE (*, ivar) C Assign statement label 200 to ivar ASSIGN 200 TO ivar C Use ivar as the target label of an assigned GOTO statement GOTO ivar WRITE (*, *)' This is never written' 200 CONTINUE WRITE (*, *)' This is written' 100 FORMAT (' This is format 100') END


Assignment (Computational)

Action Evaluates an expression and assigns the result to the specified variable. Syntax variable = expression Parameter Description variable A variable, array, array-element, or structure-element reference expression Any expression Remarks The variable and expression types must be compatible. If the types are not identical, the data type of is converted to the data type of . Logical expressions of any byte size can be assigned to logical variables of any byte size without changing the value of . Examples The following program demonstrates assignment statements: REAL a, b, c LOGICAL abigger CHARACTER*5 assertion c = .01 a = SQRT (c) b = c**2 assertion = 'a > b' abigger = (a .GT. b) WRITE (*, 100) a, b 100 FORMAT (' a =', F7.4, ' b =', F7.4) IF (abigger) THEN WRITE (*, *) assertion, ' is true.' ELSE WRITE (*, *) assertion, ' is false.' END IF END The program above has the following output: a = .1000 b = .0001 a > b is true. The following fragment demonstrates legal and illegal assignment statements: INTEGER i, int REAL rone(4), rtwo(4), x, y COMPLEX z CHARACTER char6*6, char8*8 i = 4 x = 2.0 z = (3.0, 4.0) rone(1) = 4.0 rone(2) = 3.0 rone(3) = 2.0 rone(4) = 1.0 char8 = 'Hello,' C The following assignment statements are legal: i = rone(2) int = rone(i) int = x y = x y = z y = rone(3) rtwo = rone rtwo = 4.7 char6 = char8 C The following assignment statements are illegal: char6 = x + 1.0 int = char8//'test' y = rone


AUTOMATIC

Action Declares specified variables on the stack, rather than at a static memory location. Syntax AUTOMATIC [names] Parameter Description names A list of variables or array names to be made automatic. Separate multiple names with commas. Remarks All variables are static by default. If an AUTOMATIC statement contains no variable names, all the variables within that program unit that can legally be automatic are implicitly automatic. Common-block names and variables are not allowed in an AUTOMATIC statement. A variable cannot appear in both a SAVE statement and an AUTOMATIC statement. Variables with the ALLOCATABLE, EXTERNAL, FAR, or HUGE attribute cannot be automatic. Formal arguments may not be declared automatic. A variable that has been explicitly declared automatic may not appear in a DATA or EQUIVALENCE statement. Variables that are implicitly automatic and appear in a DATA statement will be initialized and placed in static memory. A variable may appear in an AUTOMATIC statement only once. Formal arguments and procedure names may not appear in an AUTOMATIC statement. See Also: 4{Y | N}a compiler option Example C In this Example, all variables within the program unit C are automatic, except for "clark" and "lois"; these are C explicitly declared in a SAVE statement, and thus have C static memory locations: INTEGER FUNCTION Fibonacci (clark, lois) AUTOMATIC SAVE clark, lois ... END


BACKSPACE

Action Positions a file at the beginning of the preceding record. Syntax BACKSPACE {unitspec | ([UNIT=]unitspec [, ERR=errlabel] [, IOSTAT=iocheck])} If UNIT= is omitted, must be the first parameter. The parameters can otherwise appear in any order. Parameter Description unitspec An integer expression specifying an external unit. errlabel The label of an executable statement in the same program unit. An I/O error causes transfer of control to the statement at . If is omitted, the effect of an I/O error is determined by the presence or absence of . iocheck An integer variable that returns zero if there is no error, or the error number if an error occurs. Remarks The BACKSPACE statement is not legal with a file that has been opened with MODE='WRITE'. The BACKSPACE statement backs up one record, except in the following special cases: Special Case Result No preceding record The file position is not changed Preceding record is The file is positioned before end-of-file record the end-of-file record File position is The file is positioned to the in middle of record start of that record Examples BACKSPACE 5 BACKSPACE (5) BACKSPACE lunit BACKSPACE (UNIT = lunit, ERR = 30, IOSTAT = ios)


BLOCK DATA

Action Identifies a block-data subprogram, where variables and array elements in named common blocks can be initialized. Syntax BLOCK DATA [blockdataname] Parameter Description blockdataname A unique global name for the subprogram. Remarks The BLOCK DATA statement must be the first statement in a block-data subprogram. Only one unnamed block-data subprogram may appear in an executable program. The following restrictions apply: * The only statements that may be used in a block-data subprogram are BLOCK DATA, COMMON, DATA, DIMENSION, END, END MAP, END STRUCTURE, END UNION, EQUIVALENCE, IMPLICIT, MAP, PARAMETER, RECORD, SAVE, STRUCTURE, UNION, and type statements. No executable statements are permitted. * Only an entity defined in a named common block may be initially defined in a block-data subprogram. * All the constituents of a named common block must be specified in that block-data subprogram, even if not all of the constituents are initialized. Examples C The following block-data subprogram initializes C the named common block /greatlakes/: C INTEGER*2 erie, huron, michigan, ontario, superior BLOCK DATA Lakes COMMON /greatlakes/ erie, huron, michigan, ontario, superior DATA erie, huron, michigan, ontario, superior /1, 2, 3, 4, 5/ END C C Using the same common block, /greatlakes/, the C following block-data subprogram is NOT allowed; C not all the members of /greatlakes/ are specified. BLOCK DATA GrLaks COMMON /greatlakes/ erie, huron, ontario, superior DATA erie, huron, ontario, superior /1, 2, 4, 5/ END


BYTE

Action Specifies the BYTE type for user-defined names. Syntax BYTE vname [ [attrs] ] [(dim)] [/values/] + [ , vname [ [attrs] ] [(dim)] [/values/] ] ... Parameter Description vname The symbolic name of a constant, variable, array, external function, statement function, or intrinsic function; or, a function subprogram or an array declarator. The parameter cannot be the name of a subroutine or main program. [attrs] A list of attributes, separated by commas. The [attrs] describe . See Also: Attributes dim A dimension declarator. Specifying declares as an array. values A list of constants and repeated constants, separated by commas. A repeated constant takes the form n*constant, where n is a positive integer constant. The option initializes . Remarks A BYTE statement confirms or overrides the implicit type of . The name is defined for the entire program unit, and cannot be defined by any other type statement in that program unit. BYTE statements must precede all executable statements. Example BYTE count, matrix(4, 4) / 4*1, 4*2, 4*4, 4*8 /


CALL

Action Invokes a subroutine. Syntax CALL sub [([actuals])] Parameter Description sub The name of the subroutine to execute. actuals One or more actual arguments. If there is more than one argument, they are separated by commas. Remarks A subroutine can be called from any program unit. A CALL statement must contain as many actual arguments as there are formal arguments in the corresponding SUBROUTINE statement (unless the C and VARYING attributes were used in declaring the subroutine), and the corresponding arguments must have the same type. FORTRAN does not support recursive subroutine calls. An alternate-return feature lets you specify the statement to which a subroutine should return control. 1. Choose the statements in the calling routine to which you wish to return control. Precede these labels with asterisks when calling the subroutine: CALL INVERT (row, column, *100, *200, *500) 2. In the corresponding SUBROUTINE, enter asterisks for the formal arguments corresponding to the label arguments in the CALL statement: SUBROUTINE INVERT (r, c, *, *, *) 3. In the subroutine, have at least one RETURN statement for each alternate return. As arguments for these RETURN statements, specify a 1 for the RETURN statement to return control to the first statement label; a 2 for the RETURN statement for the second label, and so on. Examples . . . IF (ierr .NE. 0) CALL Error (ierr) END C SUBROUTINE Error (ierrno) WRITE (*, 200) ierrno 200 FORMAT (1X, 'error', I5, ' detected') END C This example illustrates the alternate return feature: 1 CALL Boomerang (count, *10, j, *20, *30) WRITE (*, *) 'normal return' GOTO 40 10 WRITE (*, *) 'returned to 10' GOTO 40 20 WRITE (*, *) 'returned to 20' GOTO 40 30 WRITE (*, *) 'returned to 30' 40 CONTINUE . . . SUBROUTINE Boomerang (i, *, j, *, *) IF (i .EQ. 10) RETURN 1 IF (i .EQ. 20) RETURN 2 IF (i .EQ. 30) RETURN 3 RETURN


CASE

Action Marks the beginning of a statement block that executes if an item in its expression list matches the test expression in a SELECT CASE statement. Syntax CASE {DEFAULT | (expressionlist)} statementblock Parameter Description DEFAULT The keyword indicating that the following statement block is to execute if none of the expressions in any other CASE statements match the test expression constants or ranges of constants. expressionlist A list of constants or ranges of constants. The values must be of type INTEGER, LOGICAL, or CHARACTER*1. If the test expression matches one of the values, the following block of statements executes. statementblock Executable statements (may be empty). Remarks The CASE statement may only appear within the SELECT CASE...END SELECT construct. Indicate ranges by placing a colon (:) between two values (such as 5:10 or 'A':'Z'). * Omitting the low end of a range (:10 or :'Z') causes the CASE statement block to execute for any test expression with a value less than or equal to the specified upper bound. * Omitting the high end of the range executes the statement block for any test expression with a value greater than or equal to the low end given (such as 5: or 'a':). The CASE DEFAULT statement is optional. You can include only one CASE DEFAULT statement in a SELECT CASE block. See Also: SELECT CASE...END SELECT Example CHARACTER*1 cmdchar SELECT CASE (cmdchar) CASE ('0') WRITE (*, *) "Must retrieve one to nine files" CASE ('1':'9') CALL RetrieveNumFiles (cmdchar) CASE ('A', 'd') CALL AddEntry CASE ('D', 'd') CALL DeleteEntry CASE ('H', 'h') CALL Help CASE ('R':'T', 'r':'t') WRITE (*, *) "REDUCE, SPREAD and TRANSFER commands ", + "not yet supported" CASE DEFAULT WRITE (*, *) "Command not recognized; please re-enter" END SELECT


CHARACTER

Action Specifies the CHARACTER type for user-defined names. Syntax CHARACTER[*chars] vname [ [attrs] ] [*length] [(dim)][/values/] [, vname [attrs][*length] [(dim)][/values/] ]... The order of the and parameters can be reversed. Parameter Description chars The length, in characters, of the items specified in the CHARACTER statement. vname Name of the constant, variable, or function. Cannot be the name of a subroutine or main program. [attrs] A list of attributes, separated by commas. Valid attributes are: ALIAS, ALLOCATABLE, C, EXTERN, FAR, HUGE, NEAR, PASCAL, REFERENCE, VALUE. length The length, in characters, of the immediately preceding it. This value, if specified, overrides the length indicated by . dim A dimension declarator. Specifying declares as an array. values A list of constants to initialize to, separated by commas. Remarks The name is defined for the entire program unit and cannot be defined by any other type statement in that program unit. An asterisk in parentheses ((*)) as a length specifier indicates that the length is specified elsewhere. An asterisk length specifier is allowed in: 1. Character constants defined by PARAMETER statements. 2. Formal character arguments. 3. Character functions that are defined in one program unit, and referenced in another. If neither nor is specified, the length defaults to one. CHARACTER statements must precede all executable statements. Examples CHARACTER wt*10, city*80, ch CHARACTER name(10)*20, eman*20(10) CHARACTER*20 tom, dick, harry*12, tarzan, jane*34


CLOSE

Action Disconnects a specified unit. Syntax CLOSE ([UNIT=]unitspec [, ERR=errlabel] [, IOSTAT=iocheck] [, STATUS=status]) If UNIT= is omitted, unitspec must be the first parameter. The parameters can otherwise appear in any order. Parameter Description unitspec An integer expression specifying an external unit. errlabel The label of an executable statement in the same program unit. An I/O error causes transfer of control to the statement at . If is omitted, the effect of an I/O error is determined by the presence or absence of . iocheck An integer variable that returns zero if there is no error, or the error number if an error occurs. status File status, either 'KEEP' or 'DELETE'. Remarks Files opened without a file name are scratch files. For such files the default is 'DELETE'. Specifying STATUS='KEEP' for scratch files causes a run-time error. The default for for all other files is 'KEEP'. Any files still open at program termination are automatically closed according to their default status. Closing unit 0 automatically reconnects unit 0 to the keyboard and screen. Closing units 5 and 6 automatically reconnects those units to the keyboard or screen, respectively. Closing the asterisk (*) unit causes a compile-time error. If a parameter of the CLOSE statement is an expression that calls a function, that function must not cause an I/O operation or the EOF intrinsic function. If these functions are called, the results are unpredictable. For QuickWin applications, STATUS='KEEP' causes the child window associated with the unit to remain open until the user closes the window or terminates the application. Example C Close and discard file: CLOSE (7, STATUS = 'DELETE')


COMMON

Action Shares variables between two or more program units. Syntax COMMON [/[cname] [ [attrs] ]/] nlist [ [,]/[cname][attrs]/nlist ]... Parameter Description cname A name for the common block. [attrs] A list of attributes, separated by commas. Valid attributes are: ALIAS, C, FAR, NEAR, and PASCAL. nlist A list of variable names, array names, and array declarators, separated by commas. Formal-argument names, function names, automatic variables, and allocatable arrays cannot appear in a COMMON statement. Remarks A common block can appear more than once in the same program unit. If two common blocks have the same name, the second is treated as a continuation of the first. The length of a common block equals the number of bytes required to hold all elements in that common block. If several program units refer to the same named common block, the common block must be the same length in each program unit. The blank common block can have a different length in different program units. Example PROGRAM MyProg COMMON i, j, x, k(10) COMMON /mycom/ a(3) . . . END SUBROUTINE MySub COMMON pe, mn, z, idum(10) COMMON /mycom/ a(3) . . . END


COMPLEX

Action Specifies the COMPLEX type for user-defined names. Syntax COMPLEX [*bytes] vname [ [attrs] ] [*length][(dim)][/values/] [,vname [ [attrs] ] [*length][(dim)][/values/] ]... The order of the and parameters can be reversed. Parameter Description bytes The length, in bytes, of the names in the COMPLEX statement. Must be 8 or 16. Can be overridden by the parameter. vname Name of the constant, variable, or function. Cannot be the name of a subroutine or a main program. [attrs] A list of attributes separated by commas. Valid attributes are: ALIAS, ALLOCATABLE, C, EXTERN, FAR, HUGE, NEAR, PASCAL, REFERENCE, VALUE. length Length of , in bytes. Must be 8 or 16. If given, it overrides the length specified by . dim A dimension declarator. Specifying declares as an array. values A list of constants to initialize to, separated by commas. Remarks The name is defined for the entire program unit and cannot be defined by any other type statement in that program unit. COMPLEX statements must precede all executable statements. DOUBLE COMPLEX and COMPLEX*16 represent the same data type. Examples COMPLEX ch, zdif*8, xdif*16 COMPLEX*8 zz COMPLEX*16 ax, by COMPLEX x*16, y(10)*8, z*16(10)


CONTINUE

Action Does not have any effect. Syntax CONTINUE Remarks The CONTINUE statement is a convenient place for a label, particularly as the terminal statement in a DO or DO WHILE loop. Example DIMENSION narray(10) DO 100, n = 1, 10 narray(n) = 120 100 CONTINUE


CYCLE

Action Within a loop, advances control to the terminating statement of a DO or DO WHILE loop. Syntax CYCLE Remarks The CYCLE statement skips over the remaining part of a DO or DO WHILE loop. Example Suppose you wanted to print a table of relativistic time-dilation factors for every velocity from 0 to the speed of light, in steps of 100 km/second. Perhaps you do not want to calculate these factors for speeds less than 10 percent of the speed of light. The following example computes the time-dilation factors accordingly, putting them in the array timedilation. You can use the WRITE statement to print out the array. ___________ Time-dilation factor: 1 / û 1 - (v/c)ý INTEGER sub ! subscript for timedilation array REAL timedilation(0:300) speedolight = 300000e3 ! 300000 km per second speedstep = 100e3 ! 100 km per second sub = speedolight / speedstep DO velocity = 1, speedolight, speedstep timedilation(sub) = 1.0 IF (velocity .LT. (0.1 * speedolight)) CYCLE timedilation(sub) = + 1.0 / SQRT (1.0 - (velocity / speedolight)**2) END DO


DATA

Action Assigns initial values to variables. Syntax DATA nlist /clist/ [ [,] nlist /clist/]... Parameter Description nlist A list of variables, strings or implicit DO lists to initialize. Separate list items with commas. clist A list of initial values for the items in . Values must be constants or Hollerith constants, separated by commas. Remarks Structure variables may not appear in DATA statements but structure elements may. Variables explicitly declared as automatic may not appear in a DATA statement. Only local variables, arrays, and array elements can appear in a DATA statement. The form of an implied-DO list is as follows: (dolist, dovar = start, stop [, inc]) Parameter Description dolist A list of array-element names and implied-DO lists dovar An integer variable start, stop, Integer-constant expressions inc For example, the following are implied-DO lists: (count(i), i = 5, 15, 2) ((array(sub,low), low = 1, 12), sub = 1, 2) ((result(first,second), first = 1, max), second = 1, upper) The number of iterations and the values of are established from , , and the same as for a DO loop except that the iteration count must be positive. When an implied-DO list appears in a DATA statement, the list items in are initialized once for each iteration of the implied-DO list. Examples INTEGER n, order, alpha, list(100) REAL coef(4), eps(2), pi(5), x(5,5) CHARACTER*12 help DATA n /0/, order /3/ DATA alpha /'A'/ DATA coef /1.0, 2*3.0, 1.0/, eps(1) /.00001/ C The following example initializes diagonal and below in C a 5x5 matrix: DATA ((x(j,i), i=1,j), j=1,5) / 15*1.0 / DATA pi / 5*3.14159 / DATA list / 100*0 / DATA help(1:4), help(5:8), help(9:12) /3*'HELP'/


DEALLOCATE

Action Frees the array storage space previously reserved in an ALLOCATE statement. Syntax DEALLOCATE (arraylist [, STAT = ierr]) Parameter Description arraylist A list of allocatable array names separated by commas. ierr An integer returning the error status. Remarks The STAT= parameter must appear last. Attempting to deallocate an array that was not allocated causes a run-time error. Any deallocation failure causes a run-time error, unless the STAT= parameter is present. The variable returns a value of zero if the deallocation was successful, and the number of the run-time error if the deallocation failed. Example INTEGER dataset[ALLOCATABLE](:,:,:) INTEGER reactor, level, points, error DATA reactor, level, points / 10, 50, 10 / ALLOCATE (dataset(1:reactor,1:level,1:points), STAT = error) DEALLOCATE (dataset, STAT = error)


DIMENSION

Action Declares a variable as an array and specifies its dimensions and bounds. Syntax DIMENSION array [ [attrs] ] ({ [lower:] upper | : } [,{[lower:]upper | :}... ]) Parameter Description array Array name. Separate multiple arrays with commas. [attrs] A list of attributes separated by commas. Valid attributes are: ALIAS, ALLOCATABLE, C, EXTERN, FAR, HUGE, NEAR, PASCAL, REFERENCE, VALUE. lower Lower dimension bound. Default is one. upper Upper dimension bound. Greater than or equal to bound. Remarks You can use any of the following as dimension bounds: Bound Description Arithmetic constant Produces an array with a constant size. The arithmetic value is truncated to an integer. Nonarray-integer formal Produces an adjustable-size array with argument or nonarray- dimensions equal to the initial value integer variable in a of the variable upon entry to the common block in the same subprogram. program unit An arithmetic Produces an adjustable-size array with expression dimensions equal to the expression. The expression is truncated to an integer. Expressions cannot contain references to functions or array elements. An asterisk (*) Produces an assumed-size array in a subprogram with dimension size the same as the array in the calling program. Can only be used as in the last dimension of . If is an asterisk, then array is an "assumed- size" array. The following DIMENSION statement defines an assumed-size array in a subprogram: DIMENSION data (19,*) At execution time, the array data is given the size of the corresponding array in the calling program. Within noncharacter arrays, all elements begin on even-byte (word) addresses. Within character arrays (and arrays of INTEGER*1 or LOGICAL*1 variables), elements always begin at the next available byte (odd or even). All adjustable- and assumed-size arrays, as well as the bounds for adjustable-size arrays, must be formal arguments to the program unit in which they appear. Allocatable arrays must not be formal arguments. Examples The following program dimensions two arrays: DIMENSION a(2,3), v(10) CALL Subr (a, 2, v) . . . END SUBROUTINE Subr (matrix, rows, vector) REAL MATRIX, VECTOR INTEGER ROWS DIMENSION MATRIX (ROWS,*), VECTOR (10), + LOCAL (2,4,8) MATRIX (1,1) = VECTOR (5) . . . END The following program uses assumed- and adjustable-size arrays: REAL magnitude, minimum INTEGER vecs, space, vec C Array data values are assigned in column-major order DIMENSION vecs(3, 4) DATA vecs /1,1,1,2, 1,0,3,4, 7,-2,2,1 / C Find minimum magnitude minimum = 1E10 DO 100 vec = 1, 4 C Call the function magnitude to calculate the magnitude of C vector vec. minimum = AMIN1(minimum, magnitude(vecs, 3, vec)) 100 CONTINUE WRITE (*, 110) minimum 110 FORMAT (' Vector closest to origin has a magnitude of', + F12.6) END C Function returns the magnitude of the j-th column vec in a C matrix. Note that, because of the assumed-size array, the C subroutine does not need to know the number of columns in C the matrix. It only requires that the specified column C vector be a valid column in the matrix. The number of rows C must be passed so the function can do the sum. REAL FUNCTION Magnitude (matrix, rows, j) REAL sum INTEGER matrix, rows, i, j DIMENSION matrix (rows,*) sum = 0.0 DO 100 i = 1, rows sum = sum + matrix(i,j)**2 100 CONTINUE magnitude = SQRT (sum) END


DO

Action Repeatedly executes the statements following the DO statement through the end of the loop. Syntax DO [label [,] ] dovar = start, stop [, inc] Parameter Description label The statement label of an executable statement. dovar An integer, real, or double-precision variable. start, stop The integer, real, or double-precision expressions. inc A nonzero increment for the DO variable (defaults to one). Remarks The


Return to Prof. Nam Sun Wang's Home Page
Return to Computer Methods in Chemical Engineering (ENCH250)

Computer Methods in Chemical Engineering -- FORTRAN Syntax
Forward comments to:
Nam Sun Wang
Department of Chemical & Biomolecular Engineering
University of Maryland
College Park, MD 20742-2111
301-405-1910 (voice)
301-314-9126 (FAX)
e-mail: nsw@umd.edu ©1996-2006 by Nam Sun Wang
UMCP logo