APPENDIX 2

Summary of Fortran 77 statements

Introduction

Those statements we do not recommend have been indicated with the question mark "?" and in serious cases even with two question marks "??".

Specification of program units:

  PROGRAM      - main program
 
  FUNCTION     - function,  FUNCTION can be preceded
                 by some of the specifications of the  
                 variables below, except IMPLICIT

  SUBROUTINE   - subroutine

??ENTRY        - extra entry in subprograms

? BLOCK DATA   - common data, usually given initial values

Specification of variables:

 IMPLICIT      - default IMPLICIT REAL(A-H, O-Z), INTEGER(I-N)

 IMPLICIT NONE - not standard, but very useful, it is available 
	         in Fortran 90. Gives the "Pascal convention" 
                 that all variables have to be specified. For 
		 Sun and DEC the same effect can be obtained 
		 with the switch -u in the compilation command

 INTEGER
 REAL
 DOUBLE PRECISION
 COMPLEX
 LOGICAL
 CHARACTER       CHARACTER*4

Additional specifications:

  DIMENSION    - can also be given directly in the type specification,
                 as well as in a COMMON

? COMMON       - common storage area for variables that are
                 in several program units

??EQUIVALENCE  - common storage area for several variables in the
                 same program unit

  PARAMETER    - makes a variable into a constant with a certain value

  EXTERNAL     - tells the  system that the identifier is an
                 external function or an external subroutine

  INTRINSIC    - tells the system that the identifier is an
                 intrinsic function (or a subroutine, only in
                 Fortran 90)

  SAVE         - saves the values between exit or return from one
                 subroutine into the new call of the same
                 subroutine or function

  DATA         - puts initial values into variables

Executable GOTO statements:

  GOTO snr1    - ordinary GOTO statement (jumps to the statement with
                 number snr1)

? GOTO (snr1, snr2, snr3), integer_expression
               - conditional GOTO statement. If the integer
                 expression is 1, 2 or 3, execution jumps to
                 statement number snr1, snr2 or snr3 (an arbitrary
                 number of statement numbers snr are permitted).

??GOTO statement_number_variable, (snr1, snr2, snr3)
               - an assigned GOTO statement, jumps to the statement
                 number that equals the statement
                 number variable (an arbitrary  number of
                 statement numbers snr are permitted).

??GOTO statement_number_variable
               - this is an assigned ordinary GOTO statement, it is a
                 combination of the first one, GOTO snr1, and
                 previous one, GOTO statement_number_variable without
                 a list of permitted alternatives.

??ASSIGN statement_number TO statement_number_variable
               - statement number variables can not be assigned with
                 an ordinary assignment of the type (integer
                 variable = integer expression), it has to be
                 done with the ASSIGN statement.  The statement
                 number variable can then be used for an assigned
                 GOTO statement and in the ordinary GOTO statement
                 and also in connection with FORMAT.

? IF (numerical_expression) snr1, snr2, snr3
               - arithmetical IF-statement, jumps to statement number
                 snr1 if the expression is negative,
                 snr2 if the expression is zero,
                 snr3 if the expression is positive

Other executable statements:

  IF(logical_expression)  statement
               - conditional statement: if the logical expression
                 is true, the statement is performed, in the
                 other case execution jumps directly to the next
                 statement.  The statement here is permitted to
                 be an ordinary assignment statement or an
                 ordinary jump statement (GOTO statement) or a
                 call of a subroutine.

  IF(logical_expression) THEN  ! Complete alternative statement.
             ...statements...  ! Variants without the ELSE-part as well
      ELSE                     ! as with nested ELSE, or with
             ...statements...  ! ELSE replaced by
  ENDIF  		       ! ELSE IF (log_expr) THEN
		               ! also exist.

  CONTINUE     - continuation, does nothing. It is recommended for
                 clean conclusion of a DO-loop.

  STOP         - concluding statement, stops execution.

  END          - concluding statement, stops compilation of the
                 program unit and  also  execution if it is
                 in  the main program. 
                 If END is found during execution of a subprogram,
                 an automatic return to the calling program unit
                 is executed (replaces the explicit RETURN statement).

? PAUSE        - pause statement, stops execution temporarily
                 (implementation dependent).

  DO statement_number variable = var1, var2, var3
               - DO-loop.  
                 Floating-point numbers are permitted as variables 
                 in the DO-loop, but they are not recommended.
                 It is preferable to use integers.

Input/output statements:

  OPEN         - open a file before the program can use it.
  CLOSE        - close a file.  A  file that has not been closed can
                 usually not be read.
  READ         - input
  WRITE        - output
  PRINT        - previously output to line printer, now a synonym to
                 WRITE. It works on a standard unit.
  INQUIRE      - inquires about file status.
  REWIND       - rewinds a file to the beginning.
  BACKSPACE    - rewinds a file one record.
  ENDFILE      - marks end of file.
  FORMAT       - Fortran speciality (see below).

Call statements:

  CALL sbrtn   - call a subroutine sbrtn.
  fnctn        - a function is called by giving the function
                 name fnctn.
  RETURN       - return from the subprogram (subroutine or
                 function).

FORMAT-letters:

                      Example    Comments
-------------------------------------------------------------------
Integer           I     I5       5 positions reserved
-------------------------------------------------------------------
Floating-point    F     F8.3     8 positions, out of which 3 are
   number                        used for the fractional part
                  E     E14.6    14 positions of which
                                 6 are used for the decimals
                                 4 - for the exponent
                                 1 - for the sign
                                 1 - for the starting zero
                                 1 - for the decimal point
                                 1 - for a blank character
                  D     D20.12   as E, but for double precision
                  G     G14.6    as F, if the number can  be  given
                                 within the field, else as E
-------------------------------------------------------------------
Complex numbers                  as a pair of floating-point variables
-------------------------------------------------------------------
Logical          L      L1
Character        A      A7            7 characters are available in A7
  string                        
                 ' '    'Example'     Conventional character constant
                 nH     7HExample     Hollerith constant (obsolete)
Positioning      Tn                   n positions from the left
                 TLn                  n positions towards left
                 TRn                  n positions towards right
                 nX                   n positions towards right
No new line      $                    this is used if you wish to
                                      do input in direct connection
                                      with an  output, to stay on
                                      the same line. Not standard!
                                      Not Fortran 90!
Discontinue      :                    if the list does not contain
                                      any more elements  the
                                      format is also finished here
New record       /                    normally a new line
-------------------------------------------------------------------
Binary           B                    not Fortran 77 but Fortran 90
Octal            O                    not Fortran 77 but Fortran 90
Hexadecimal      Z                    not Fortran 77 but Fortran 90
-------------------------------------------------------------------
Output           SP                   + is written
                 SS                   + is not written
                 S                    standard (normal SS)
In all alternatives a minus - is written for negative values
-------------------------------------------------------------------
Input            BZ                   blanks  are  interpreted  as
                                      zeroes
                 BN                   blanks are  not  regarded  as
                                      anything (blanks are skipped)

 BN is standard using the ULTRIX, when punched cards were used,
 BZ was the standard. Compare with BLANK = "ZERO" and
 Blank = "NULL" in the OPEN-statement.
-------------------------------------------------------------------
Scaling factor kP:
Input:                                with an exponent, no action.
                                      Without exponent, the number
                                      is multiplied by 10**(-k)
                                      before assignment, which means
                                      a change of the value.
Output:                               with exponent, the mantissa
                                      is multiplied by 10**k  and the
                                      exponent is reduced with k,
                                      which means no change of the
                                      value.
                                      Without exponent, the
                                      number is multiplied by 10**k
                                      before the output, which means
                                      a change of value.
NB! S, SP, SS, BN, BZ and kP are valid until the end of the FORMAT or until a new one of the same kind appears. To scale with kP is good with E-format on output, because then you avoid that the first digit is zero, and you get more information into less space on the paper. To scale with kP is catastrophic using F-format, but it was of great interest when punched cards were still in use.

A very good and complete description of input and output in Fortran, including the use of the FORMAT-letters, is given in the book by Adams et al (1992).

Extension in Fortran 90 regarding the FORMAT-letters:

You can now replace E as the mark for output in exponential form by ES and then you get the Scientific form with output of one digit different from zero before the decimal point. If you instead replace E by EN you get an ENgineering form with one to three digits before the decimal point and the exponent evenly divisible by three. If the output value is zero you get the same output from ES and EN as from E.

Another extension is that the FORMATs I, B, O, and Z may be written Iw.m, Bw.m, Ow.m, and Zw.m, where w is the usual field width, and the optional m indicates the minimum number of digits, with leading zeros as necessary.

Addition regarding input/output:

Most of these have a large number of parameters in the so-called control list which has been expanded considerably in Fortran 90. They are treated shortly in five pages of NAG (1992) and are ACCESS, ACTION, ADVANCE, APPEND, APOSTROPHE, ASIS, BLANK, DELETE, DELIM, DIRECT, END, EOR, ERR, EXIST, FILE, FMT, FORM, FORMATTED, IOLENGTH, IOSTAT, KEEP, NAME, NAMED, NEXTREC, NEW, NML, NO, NULL, NUMBER, OLD, OPENED, PAD, POSITION, QUOTE, READ, READWRITE, REC, RECL, REPLACE, REWIND, SCRATCH, SEQUENTIAL, SIZE, STATUS, UNDEFINED, UNFORMATTED, UNIT, UNKNOWN, WRITE, YES and ZERO.

Addition concerning output on paper:

In order to provide a possibility to request for example the top of the next page there has for many years existed "ASA carriage control characters", which are described in ISO (1991), section 9.4.5, and in ANSI (1978), section 12.9.5.2.3. Using UNIX most output is to a monitor, and the ASA characters are not of interest. If you wish to use the control characters for output on paper you first have to write on a file, which is then printed with the tool fpr if you are using DEC, Hewlett Packard or Sun, but a tool called asa if you use Cray or Silicon Graphics. It is used in the following way
   fpr < output_file | lpr -Pprinter
where output_file is the name of the file to be printed with control characters and printer is the name of the printer to be used.

Further information on the ASA Control Characters are now available.

Locally we now have a problem in Linköping, since all output is performed via PostScript. We therefore recommend you to to use fpr in the following way

	fpr < output_file > output_file2

	ens output_file2
In the dialogue from the utility ens you reply Landscape if you wish to get the output on wide paper.


Last modified: 17 August 1999
boein@nsc.liu.se