programming with fortran

114
AE6382 The Future

Upload: kalpesh-karkeli

Post on 11-Dec-2015

262 views

Category:

Documents


11 download

DESCRIPTION

This is good !

TRANSCRIPT

Page 1: Programming With Fortran

AE6382

The Future

Page 2: Programming With Fortran

AE6382

Introduction to FORTRAN

History and purpose of FORTRAN FORTRAN essentials

Program structure Data types and specification statements Essential program control FORTRAN I/O subfunctions and subroutines

Extensions for Fortran 95 Pitfalls and common coding problems Sample problems

OBJECTIVES

Page 3: Programming With Fortran

AE6382

FORTRAN History

One of the oldest computer languages created by John Backus and released in 1957 designed for scientific and engineering computations

Version history FORTRAN 1957 FORTRAN II FORTRAN IV FORTRAN 66 (released as ANSI standard in 1966) FORTRAN 77 (ANSI standard in 1977) FORTRAN 90 (ANSI standard in 1990) FORTRAN 95 (ANSI standard version) FORTRAN 2003 (ANSI standard version)

Many different “dialects” produced by computer vendors (Digital VAX Fortran, now Intel Fortran)

Large majority of existing engineering software is coded in FORTRAN (various versions)

Page 4: Programming With Fortran

AE6382

Statement Format

FORTRAN before 90 requires a fixed format

Based on the punch card in use when Fortran was created

PROGRAM MAIN

C COMMENTS ARE ALLOWED IF A “C” IS PLACED IN COLUMN #1

DIMENSION X(10)

READ(5,*) (X(I),I=1,10)

WRITE(6,1000) X

1000 FORMAT(1X,’THIS IS A VERY LONG LINE OF TEXT TO SHOW HOW TO CONTINUE ’

* ‘THE STATEMENT TO A SECOND LINE’,/,10F12.4)

1-5Label

6 7-72 Statements 73-80OptionalLine #s

Any character: continuation line

Page 5: Programming With Fortran

AE6382

Statement Format

FORTRAN fixed format “C” in column 1 indicates that line is a comment columns 1-5 are reserved for statement labels

– statement labels are not required unless the statement is the target of a goto

– labels are numeric values only column 6 is the continuation flag

– any character in column 6, other than space or “0”, indicates that this line is a continuation of the previous line

– there is usually a limit of 19 on the number of continuations columns 7-72 are contain Fortran statements columns 73-80 is for sequence information

– only of any use when using punch cards

Page 6: Programming With Fortran

AE6382

Statement Format

IBM punch card

Page 7: Programming With Fortran

AE6382

Building a FORTRAN Program

FORTRAN is a complied language (like C) so the source code (what you write) must be converted into machine code before it can be executed (e.g. Make command)

FORTRANProgram

FORTRANCompiler

Libraries

Link withLibraries

Executable File

Source Code Object CodeExecutable

Code

ExecuteProgram

Test & DebugProgram

Make Changesin Source Code

Page 8: Programming With Fortran

AE6382

Structure of a Fortran Program

Fortran is a compiled language all memory is allocated statically at compile time

– there is no standard method for allocating additional memory in a Fortran program before Fortran 90

– memory is allocated in a predictable manner, a fact which can be used by the programmer to his advantage or distress

there is no official recursion before Fortran 90– some vendor implementations had recursive capabilities– static memory allocation is at odds with the use of a stack which is

needed for recursion Fortran does not guarantee value of un-initialized memory

Page 9: Programming With Fortran

AE6382

Structure of a Fortran Program

Fortran consists of program units program function subroutine block data

The program unit contains the main code and the point where execution starts in Fortran 77 a program begins with the program statement earlier versions of Fortran did not have a program statement

unless a vendor dialect provided one the end statement terminates the program unit

Page 10: Programming With Fortran

AE6382

Fortran Program

The program unit contains the main code and the point where execution starts in Fortran 77 a program begins with the program statement earlier versions of Fortran did not have a program statement

unless a vendor dialect provided one the end statement terminates the program unit

– marks end of statements that belong to program– during execution it will cause the program to halt

a program unit may contain internal sub-programs– internal functions– internal subroutines

Page 11: Programming With Fortran

AE6382

Fortran Subroutine

The subroutine unit contains Fortran code that can be called from other Fortran code

a subroutine begins with a subroutine statement contains a name for the subroutine a list of formal arguments

subroutines may be internal or external an internal subroutine is included in the code of program unit

and is only callable by the program an external subroutine is created outside of a program unit and

is callable from everywhere

Page 12: Programming With Fortran

AE6382

Fortran Subroutine

SUBROUTINE MULT(A,B,C)

C = A * B

RETURN

END

CALL MULT(5.0,X,VALUE)

Page 13: Programming With Fortran

AE6382

Fortran Function

The function unit contains Fortran code that can be called from other Fortran code

It differs from a subroutine in that it returns a value a subroutine begins with a function statement

contains a name for the function a list of formal arguments specifies a return type

functions may be internal or external an internal function is included in the code of program unit and is

only callable by the program an external function is created outside of a program unit and is

callable from everywhere

Page 14: Programming With Fortran

AE6382

Fortran Function

REAL FUNCTION MULT(A,B)

MULT = A * B

RETURN

END

VALUE = MULT(5.0,X)

Page 15: Programming With Fortran

AE6382

Fortran Block Data

The Block Data program unit does not contain any executable code

Used to initialize memory in common blocks It is not “called” by any code in the program, it contains

instructions for the initializing memory when the program is loaded into memory for running

Page 16: Programming With Fortran

AE6382

Fortran Block Data

BLOCK DATA

COMMON/MEM/A,B

DATA A,B/10.0,-3.14/

END

Page 17: Programming With Fortran

AE6382

Fortran Program Organization

Program units have a statement order header (program, subroutine, function, block data) declarations (variables and types) data initialization (data statements) executable statements (and format statements) internal subprogram units end statement

Page 18: Programming With Fortran

AE6382

Fortran Variable

Variables represent the memory of the program Fortran variables

Fortran IV numbers and letters, at least 6 characters Fortran 77 numbers and letters and “_”, at least 16 characters must start with a letter

Up through 77, spaces in a Fortran program are ignored IVALUE and I VAL UE are the same using strange spacing, while acceptable, is bad practice

Fortran variables are typed Fortran is case insensitive

ivar is the same as IVAR or IvAr

Page 19: Programming With Fortran

AE6382

Fortran Variable Typing

All Fortran variables are typed INTEGER REAL DOUBLE PRECISION COMPLEX LOGICAL CHARACTER (77+)

Page 20: Programming With Fortran

AE6382

Fortran Variable Typing

A feature of Fortran – implicit typing when a variable appears that has not been declared previously it

is created (at compile time) it is assigned a type based on the first character of the name

– A-H,O-Z is type REAL– I-N is type INTEGER

a typo can cause the creation of a new variable – not an error

Starting with 77 the implicit statement was added allowed changing the first letter assignments most 77 compilers include the implicit none statement that

requires that all variables be explicitly typed – prevents the typo problem

It is good practice to use implicit none

Page 21: Programming With Fortran

AE6382

Fortran Variable Typing

Change implicit typing so that A becomes an INTEGER type

Disable implicit typing altogether

PROGRAM TEST

IMPLICIT INTEGER (A)

PROGRAM TEST

IMPLICIT NONE

Page 22: Programming With Fortran

AE6382

Fortran Variable Typing

In Fortran any variable can be explicitly typed In the declarations section enter a type identifier followed

by a list of variable names

The first letter implicit typing is over-ridden when explicit typing is used

A common Fortran error when using implicit typing is to use a variable such as INITIAL_VALUE as if it contained a real (floating point) value

INTEGER A,VALUE,ISTART

REAL INITIAL_VALUE

Page 23: Programming With Fortran

AE6382

Fortran Variable Typing

The types presented earlier are the default types The range of both INTEGER and REAL are dependent

on the computer architecture one computer may have a 32 bit integer while another may use

16 bit as its default

An attempt to deal with this lead to types such as REAL*8, INTEGER*4 the number after the * indicates the number of bytes used most computers have 8 bit bytes not every architecture will have every combination not a practical problem in an Intel world but knowledge of the architecture of the system where a legacy

Fortran program was developed is needed to convert to Intel

Page 24: Programming With Fortran

AE6382

Fortran Variable Typing

Fortran 90+ uses a different method to deal with number ranges that is architecture independent

Page 25: Programming With Fortran

AE6382

Fortran Variable Typing

The CHARACTER type was introduced in 77 The * notation is used to specify the maximum number

of characters the variable can hold

Before 77 the Hollerith notation was used common in older Fortran code, even in some 77 code normally placed characters into INTEGER arrays required knowledge of byte length of the variable portability problem

CHARACTER*20 TITLE

INTEGER*4 TITLE(5)

DATA TITLE/4Habcd,4Hefgh,…/

Page 26: Programming With Fortran

AE6382

Fortran Arrays

The array is the only data structure supported in 77 and before

An array is a linear allocation of memory An array can contain up to 7 dimensions Arrays are indexed starting a 1

INTEGER A

DIMENSION A(10

INTEGER B

DIMENSION B(10,10)

REAL C(10,10,10)

Page 27: Programming With Fortran

AE6382

Fortran Arrays

Fortran 77 introduced the ability to specify a lower bound for an array dimension

During execution of a Fortran program there is normally no check made on array index bounds there may be a compiler option to enable these checks some bound checking code only checks the equivalent linear

index not each individual index

INTEGER B

DIMENSION B(0:10,0:10)

Page 28: Programming With Fortran

AE6382

Fortran Arrays

Fortran character (77)

CHARACTER*10 TITLE(4)

Page 29: Programming With Fortran

AE6382

Fortran Variables and Subroutines

All arguments to a Fortran subroutine are passed by reference the subroutine receives the address of the variable any changes made by the subroutine are seen by the caller most other languages pass by value (the subroutine receives a

copy) passing an array as an argument with just the name will pass

the address of the first element

On entry to a subroutine its local variables are not guaranteed to have any known value the save statement introduced in 77 will ensure that a variable

will have on entry the value that it had on its last exit from the subroutine

Page 30: Programming With Fortran

AE6382

Fortran Common Blocks

Normally variables in a Fortran program are local to the unit in which they are declared variables may be made known to subroutines using the

arguments variables may be created in a common block

Common blocks are shared memory each program unit that declares the common block has access

to it

Page 31: Programming With Fortran

AE6382

Fortran Common Blocks

Two types of common blank common – unnamed named common

Most systems do not allow blank common to be initialized

Blank common can sometimes be used to allocate unused memory (depends on OS)

COMMON A,B(10),C

COMMON/SET1/A,B(50,5),C

Page 32: Programming With Fortran

AE6382

Fortran Common Blocks

Problems each program unit that declares access to a common block

defines it’s own view– type of each variable in the block– size of each array in the block

when views between units differ there can be problems – some linkers will warn of size differences

PROGRAM TEST

COMMON/A/A,B(10),C

END

SUBROUTINE DOIT

COMMON/A/I,J(5),K(20)

END

Page 33: Programming With Fortran

AE6382

Fortran Equivalence

The EQUIVALENCE statement is used to alias a memory location

Usually will include a type change Also used to provide aliases for elements of an array

Takes advantage of no index checking

INTEGER A(100)

EQUIVALENCE (INCREMENT,A(4))

COMMON A(10000)

INTEGER IA(1)

EQUIVALENCE (IA(1),A(1))

Page 34: Programming With Fortran

AE6382

Fortran Parameter

The PARAMETER statement is used to define constants

A parameter can be used wherever a variable is expected – but cannot be overwritten

Can be used in declarations

PARAMETER (MAX=20)

PARAMETER (MAX=1000)

INTEGER A(MAX)

Page 35: Programming With Fortran

AE6382

Fortran Literals

Literals are constants that appear in a Fortran program Number

integers - 1, -34 real - 1.0, 4.3E10, 5.1D-5 complex – (5.2,.8)

Other logical - .true., .false. character – ‘title line’

Obsolete but still lurking in code Hollerith – 4Habcd, 8Habcdef

Page 36: Programming With Fortran

AE6382

Fortran Literals

INTEGER A

A = 34

REAL A(20)

A(1) = 31.4159E-1

ITERM = -10.3

COMPLEX Z

Z = (10,-10.5)

REAL_PART = REAL(Z)

AIMAG_PART = AIMAG(Z)

Z = CMPLX(REAL_PART * 2,AIMAG_PART)

Page 37: Programming With Fortran

AE6382

Fortran Expressions

Expressions are the heart of Fortran (Formula Translator)

There are two types of expressions numeric

– 2 * 3.14159 * RADIUS**2– SIN(PI)

logical– IBOOL = .TRUE.– I .EQ. 10 .AND. ISTOP

• note: LOGICAL ISTOP

Page 38: Programming With Fortran

AE6382

Fortran Numerical Operators

The numerical operators ** (exponentiation) * / unary + - binary + -

Parentheses are used to alter the order of evaluation For binary operators, if the types do not match an implicit

conversion is performed to the most general type– integer -> real -> double precision– anything -> complex

Page 39: Programming With Fortran

AE6382

Fortran Numerical Operators

WARNING: division of an integer by an integer will produce a truncated result

– 5 / 2 => 2 not 2.5– FLOAT(5)/2 => 2.5

The type-conversion intrinsic functions can be used to get the desired results

Page 40: Programming With Fortran

AE6382

Intrinsic Functions

Fortran includes an extensive set of built-in functions Fortran 66 has different names for these functions

depending on the return type and argument type Fortran 77 introduced generic names for intrinsic

functions

Page 41: Programming With Fortran

AE6382

Type Conversion

The intrinsic functions have two forms– generic available only in 77 and above– argument specific

Conversion to integer– INT(any) the generic version– INT(real)– IFIX(real)– IDINT(double)

Conversion to real– REAL(any) the generic version– FLOAT(integer)– REAL(integer)– SNGL(double)

Page 42: Programming With Fortran

AE6382

Type Conversion

Conversion to double– DBLE(any) the generic version

Conversion to complex– COMPLX(any) the generic version

Character to integer (77+ only)– ICHAR(character)

Integer to character (77+ only)– CHAR(integer)

Page 43: Programming With Fortran

AE6382

Truncation

To integer part, return as real or double– AINT(real or double) the generic version– AINT(real)– DINT(double)

To nearest integer, return as real or double– ANINT(real or double) the generic version– ANINT(real)– DNINT(double)

To nearest integer, return as integer– NINT(real or double) the generic version– NINT(real)– IDNINT(double)

Page 44: Programming With Fortran

AE6382

Math Functions

sine and cosine (radians)– SIN(real or double) the generic version– SIN(real)– DSIN(double)– CSIN(complex)

exponential– EXP(real or double) the generic version– EXP(real)– DEXP(double)– CEXP(complex)

natural logarithm– LOG(real or double) the generic version– ALOG(real)– DLOG(double)– CLOG(complex)

Page 45: Programming With Fortran

AE6382

Math Functions

tangent (radians)– TAN(real or double) the generic version– TAN(real)– DSIN(double)

square root– SQRT(real or double) the generic version– SQRT(real)– DSQRT(double)– CSQRT(complex)

hyperbolic sine– SINH(real or double) the generic version– SINH(real)– DSINH(double)

Page 46: Programming With Fortran

AE6382

Math Functions

there are also similar functions for arcsine, arccosine, arctangent (ASIN, ACOS, ATAN) hyperbolic sine, cosine, tangent (SINH, COSH, TANH) complex conjugate (CONJ) base10 logarithms (LOG10)

Page 47: Programming With Fortran

AE6382

Fortran Statements

The executable statements in Fortran assignment (=) branching (GOTO) comparison (IF) looping (DO) subroutine invocation (CALL)

Page 48: Programming With Fortran

AE6382

Fortran Assignment

The simple assignment statement stores the result of computations into a variable

DIMENSION A(10,10)

A(I,10) = 2.0 * PI * R**2

INTEGER A

A = A + 1

Page 49: Programming With Fortran

AE6382

Fortran Branching

Fortran includes a GOTO statement In modern languages this is considered very bad

its use was essential in Fortran 66 its predecessors Fortran 77 introduced control statements that lessened the need

for the GOTO

IF (I .EQ. 0) GO TO 100

A = 4.0 * AINIT

GOTO 200

100 B = 52.0

200 C = B * A

Page 50: Programming With Fortran

AE6382

Fortran Branching

The Fortran GOTO always branched to a Fortran statement that contained a label in columns 1-5

The labels varied from 1 to 99999 Variations of the go to statement are

assigned goto computed goto

Spaces are ignored in Fortran code before 90 GOTO and GO TO are equivalent

Excessive use of the goto (required in 66 and before) leads to difficult to understand code

Page 51: Programming With Fortran

AE6382

Fortran Branching

Assigned goto ASSIGN 100 TO TARGET

GOTO TARGET

100 CONTINUE

Page 52: Programming With Fortran

AE6382

Fortran Branching

Computed goto Operates much like a case or switch statement in other

languages GOTO (100,200,300,400),IGO

100 CONTINUE

GOTO 500

200 CONTINUE

GOTO 500

500 CONTINUE

Page 53: Programming With Fortran

AE6382

Fortran Continue

The CONTINUE statement is a do-nothing statement and is frequently used as a marker for labels

It is used most frequently with DO loops

Page 54: Programming With Fortran

AE6382

Fortran IF

The IF statement is used to perform logical decisions The oldest form is the 3-way if (also called arithmetic if) The logical if appeared in Fortran IV/66 The more modern if-then-else appeared in Fortran 77

Page 55: Programming With Fortran

AE6382

Fortran 3-way If

The 3-way if statement tested a numerical value against zero

It branched to one of three labels depending on the result IF (RADIUS) 10,20,30

10 CONTINUE

GOTO 100

20 CONTINUE

GOTO 100

30 CONTINUE

GOTO 100

100 CONTINUE

IF (ABS(RADIUS-EPS)) 10,10,20

10 CONTINUE

GOTO 100

20 CONTINUE

GOTO 100

100 CONTINUE

Page 56: Programming With Fortran

AE6382

Fortran Logical If

The logical if statement performed a test using the logical operators .EQ., .NE., .LT., .LE., .GT., .GE. .AND., .OR., .NOT.

If result is true then a single statement is executed IF (ISTART .EQ. 50) GOTO 100

100 CONTINUE

IF (IMODE .EQ. 2) A = SQRT(CVALUE)

LOGICAL QUICK

QUICK = .TRUE.

IF (QUICK) STEP=0.5

IF (.NOT. QUICK) STEP = 0.01

Page 57: Programming With Fortran

AE6382

Fortran Logical If

LOGICAL QUICK

QUICK = .TRUE.

IF (QUICK) STEP=0.5

IF (.NOT. QUICK) STEP = 0.01

IF (QUICK .AND. (ABS(XVALUE – EPS) .LT. 0.005)) GOTO 1000

Page 58: Programming With Fortran

AE6382

Fortran Modern If

Fortran 77 introduced the modern if statement (so-called structured programming)

The test operated the same as the logical if Greatly reduced the need for using the goto statement Includes

then clause else clause else if clause

Page 59: Programming With Fortran

AE6382

Fortran Modern If

This form eliminates the goto statements from the previous example

LOGICAL QUICK

QUICK = .TRUE.

IF (QUICK) THEN

STEP=0.5

ELSE

STEP = 0.01

ENDIF

IF (QUICK .AND. (ABS(XVALUE – EPS) .LT. 0.005)) THEN

END IF

Page 60: Programming With Fortran

AE6382

Fortran Modern If

This form reduces the need for the computed goto

IF (MODE .EQ. 0) THEN

ELSE IF (MODE .EQ. 1) THEN

ELSEIF (MODE .EQ. 2) THEN

ELSE

END IF

Page 61: Programming With Fortran

AE6382

Fortran Looping

The DO statement is the mechanism for looping in Fortran

The do loop is the only “official” looping mechanism in Fortran through 77

Here I is the control variable it is normally an integer but can be real 1 is the start value 10 is the end value 2 is the increment value everything to the 100 label is part of the loop

DO 100 I=1,10,2

100 CONTINUE

Page 62: Programming With Fortran

AE6382

Fortran Looping

The labeled statement can be any statement not just continue

Loop may be nested nested loops can share the same label – very bad form

DO 100 I=1,10,2

DO 100 J=1,5,1

100 A(I,J) = VALUE

DO 200 I=1,10,2

DO 100 J=1,5,1

A(I,J) = VALUE

100 CONTINUE

200 CONTINUE

Page 63: Programming With Fortran

AE6382

Fortran Looping

Before Fortran 77 a do loop would always execute at least once – despite the parameters

The increment may be negative, if not specified it is assumed to be 1

DO 100 I=10,1,2

100 CONTINUE

Page 64: Programming With Fortran

AE6382

Fortran Looping

WARNING: Through Fortran 77 there is an extended do loop can jump out of loop to code outside the loop that code can jump back into the loop valid as long as code does not modify the control variable no need to ever use it – use a subroutine instead

DO 100 I=1,100

GOTO 1000

99 CONTINUE

100 CONTINUE

1000 CONTINUE

GOTO 99

DO 100 I=1,100

CALL XYZ

100 CONTINUE

Page 65: Programming With Fortran

AE6382

Fortran Looping

Fortran 77 introduced a form of the do loop that does not require labels

The indented spacing shown is not required

DO I=1,100

ENDDO

DO I=1,100

DO J=1,50

A(I,J) = I*J

END DO

ENDDO

Page 66: Programming With Fortran

AE6382

Fortran Looping

A variant of Fortran 77 known as MIL-STD 1753 introduced a new loop construct – the while loop

While not part of the Fortran standard it is available in almost all Fortran 77 compilers

This form is an infinite loop and would require an additional test in the loop to exit

DO WHILE (I .LT. 1000)

ENDDO

DO WHILE (.TRUE.)

END DO

Page 67: Programming With Fortran

AE6382

Fortran Looping

Finally, there is a form of the do loop called the implied do loop

It is used on READ, WRITE, and DATA statements

READ(5,8000) (A(I),I=1,10)

WRITE(6,8000) ((A(I,J),I=1,10),J=1,10)

DATA ((IX(I,J),I=1,10),J=1,10)/1,2,3…/

Page 68: Programming With Fortran

AE6382

Fortran Subroutine Invocation

There are two methods by which a sub program can be called in Fortran use the CALL statement for subroutines as part of a numerical expression for a function

CALL XX(A,B,C)

SUBROUTINE XX(X,Y,Z)

END

VALUE = 4.3 * ROOT(X)

REAL FUNCTION ROOT(A)

END

Page 69: Programming With Fortran

AE6382

Fortran Subroutine Invocation

The variables on the invocation are the actual arguments The variables in the declaration are the formal

arguments More about sub programs will be covered later

Page 70: Programming With Fortran

AE6382

Miscellaneous Statements

There are several other Fortran statements RETURN will cause a sub program to return to the caller at that

point – the END statement contains an implied RETURN a number on a RETURN statement indicates that an alternate

return be taken STOP will cause a program to terminate immediately – a

number may be included to indicate where the stop occurred, STOP 2

PAUSE will cause the program to stop with a short message – the message is the number on the statement, PAUSE 5

Page 71: Programming With Fortran

AE6382

Fortran I/O Statements

Fortran contains an extensive input/output capability The relevant statements are

READ WRITE OPEN CLOSE INQUIRE REWIND BACKSPACE ENDFILE FORMAT

Fortran I/O is based on the concept of a unit number 5 is generally input – stdin on Unix 6 is usually output – stdout on Unix other unit numbers can be created as needed

Page 72: Programming With Fortran

AE6382

Fortran I/O Statements

Management of unit numbers was not specified in any system independent way before Fortran 77 older programs will just use a unit without any declaration – the

linkage to a file was performed by the OS the following usage is common

this is non-standard and can only be used as a guide when converting Fortran program to a modern OS (Linux, Unix, or Windows)

PROGRAM MAIN(INPUT,OUTPUT,TAPE5=INPUT,TAPE6=OUTPUT)

Page 73: Programming With Fortran

AE6382

Fortran I/O Statements

There are two types of I/O in Fortran formatted unformatted or binary

There are two modes of operation sequential random

Formatted I/O uses a format statement to prepare the data for output or interpret for input

Unformatted I/O does not use a format statement the form of the data is generally system dependent usually faster and is generally used to store intermediate results

Page 74: Programming With Fortran

AE6382

Fortran I/O Statements

Unformatted I/O does not use a format statement

The reverse operation is

WRITE(9) A,B,C,D,E

READ(9) A,B,C,D,E

Page 75: Programming With Fortran

AE6382

Fortran I/O Statements

The FORMAT statement is the heart of the Fortran formatted I/O system

The format statement instructs the computer on the details of both input and output size of the field to use for the value number of decimal places

The format is identified by a statement label

A format can be used any number of times The label number must not conflict with goto labels

WRITE(6,9000) A,B,C,D,E

9000 FORMAT(1X,4F8.5,2x,E14.6,//)

Page 76: Programming With Fortran

AE6382

Fortran I/O Statements

The Fortran I/O statements have a common form with a common set of parameters

The UNIT and FMT keywords can be omitted, in which case the unit and format are the first two parameters

The other parameters are all optional The list is the list of variables or expressions to be

converted to or from Fortran IV/66 only uses a unit number and a format

label, some implementations allow END

stmt(UNIT=n,FMT=label,IOSTAT=int-variable,ERR=label,END=label) list

stmt(n,label,IOSTAT=int-variable,ERR=label,END=label) list

stmt(n,label) list

Page 77: Programming With Fortran

AE6382

Fortran I/O Statements

The UNIT keyword is used to specify the device on which to perform the I/O the keyword may be omitted – the unit must be the first

parameter

The FMT keyword is used to specify a format label that will be used to control the I/O the keyword may be omitted – the format label must be the

second parameter an unformatted I/O operation does not use a format a character string may be used instead (77 only)

The NML keyword is used to specify a namelist group NML and FMT are mutually exclusive

Page 78: Programming With Fortran

AE6382

Fortran I/O Statements

The IOSTAT keyword is used to specify an integer variable that will, upon completion, contain a value that indicates how the I/O completed = 0 – there was no error or EOF condition, OK > 0 – the value is the error that occurred, this is implementation

dependent < 0 – and EOF, end of file, was encountered

The ERR keyword is used to specify a statement label that will be jumped to if an error occurs of specified, IOSTAT will contain the error code

The END keyword is used to specify a statement label that will be jumped to if an EOF condition exists

The END and ERR keywords are not required, the programmer can just test the value of IOSTAT

If IOSTAT or the END/ERR keywords are not used the Fortran library will invoke a standard error response – usually terminate the program

Page 79: Programming With Fortran

AE6382

Fortran I/O Statements

READ(5,9000) A,B,C,D,E

9000 FORMAT(1X,4F8.5,2x,E14.6,//)

READ(UNIT=5,FMT=9000,ERR=100) A,B,C,D,E

C come here on end of file

100 CONTINUE

9000 FORMAT(1X,4F8.5,2x,E14.6,//)

READ(5,’(1X,4F8.5,2x,E14.6,//)’,IOSTAT=IERR) A,B,C,D,E

IF (IERR) 100, 200, 300

C 100 – EOF, 200 – OK, 300 – an error

Page 80: Programming With Fortran

AE6382

Fortran I/O List

The I/O list is the list of variables or expressions that are to be processed by an I/O statement

Formatted I/O will perform conversions between internal binary format and external character format

Unformatted I/O does not conversion There are three forms of formatted I/O

the standard form list directed namelist directed

Page 81: Programming With Fortran

AE6382

Fortran Formatted I/O

The standard form requires the use of a format statement that is used to control the

conversion process normally used for bulk input or output

List directed, also called free format performs the conversion based on the type of the next variable

in the I/O list the format is specified as * or FMT=* frequently used for user typed input or debugging statements data separated by blanks or commas

Namelist directed conversion is controlled by variable type data is entered by name

Page 82: Programming With Fortran

AE6382

Fortran I/O Statements

READ(6,*) A,B,I

--- the input below

4.5 17 35

WRITE(6,*) ‘The value of a=‘,A

NAMELIST /CONTROL/ A,B,TITLE

INTEGER A

CHARACTER*80 TITLE

READ(5,NML=CONTROL)

--- the input below

&CONTROL

TITLE=‘A title line’

A=5

B=3.14

/

Page 83: Programming With Fortran

AE6382

Fortran I/O List

The I/O list part of the statement defines the variables to be used a READ statement must contain only variables a WRITE statement can contain constants and expressions in

addition to variables implied do-loops are permitted if an array variable is included with any indexing supplied then

an implied do-loop is implied– iterates through the entire array, left-most indices varying most

rapidly

REAL A(5,5)

READ(5,*) A

--- same as

READ(5,*) ((A(I,J),I=1,5),J=1,5)

Page 84: Programming With Fortran

AE6382

FORMAT Statement

Very powerful and versatile but can be quite tedious to master and may vary between dialects

Designed for use with line printers (not screens) Only infrequently used for input unless data format is

clearly defined and consistently applied General:

Syntax: label_no FORMAT(format-specifiers) Specifies format to be used in READ or WRITE statement that

references this label_no. format_specifiers are quite extensive and complex to master. each format specifier is separated by a comma.

Page 85: Programming With Fortran

AE6382

Format Specifiers

X format code Syntax: nX Specifies n spaces to be included at this point

I format code Syntax: Iw Specifies format for an integer using a field width of w spaces. If

integer value exceeds this space, output will consist of **** F format code

Syntax: Fw.d Specifies format for a REAL number using a field width of w

spaces and printing d digits to the right of the decimal point. A format code

Syntax: A or Aw Specifies format for a CHARACTER using a field width equal to

the number of characters, or using exactly w spaces (padded with blanks to the right if characters are less than w.

Page 86: Programming With Fortran

AE6382

Format Specifiers – cont’d

T format code Syntax: Tn Skip (tab) to column number n

Literal format code Syntax: ‘quoted_string’ Print the quoted string in the output (not used in input)

L format code Syntax: Lw Print value of logical variable as T or F, right-justified in field of

width, w.

Page 87: Programming With Fortran

AE6382

Format Specifiers – cont’d

BN format code Syntax: BN Ignore embedded blanks in a numeric field

BZ format code Syntax: BZ Treat embedded blanks in a numeric field as zero

Page 88: Programming With Fortran

AE6382

Format Specifiers – cont’d

The BN and BZ codes are Fortran 77 Before Fortran 77 blanks were treated as zero

Starting with Fortran 77 BN is the default Also set globally using OPEN(BLANK=NULL

8000 FORMAT(BN,I10)

|----+----o----+----o----+----o----+----| -1234

result: -1234

8000 FORMAT(BZ,I10)

|----+----o----+----o----+----o----+----| -1234

result: -1234000

Page 89: Programming With Fortran

AE6382

Format Specifiers – cont’d

E format code Syntax: Ew.d Print value of REAL variable using “scientific notation” with a

mantissa of d digits and a total field width of w. Ex:

E14.5 produces for the REAL value -1.23456789e+4:

You must leave room for sign, leading 0,decimal point, E, sign, and 2 digits for exponent (typically at least 7 spaces)

If specified width is too small, mantissa precision, d, will be reduced unless d<1 in which case *** will be output.

Using nP prefix will shift mantissa digit right by n and reduce exponent by –n. Ex; 1PE14.5 above yields:

|----+----o----+----o----+----o----+----| -0.12345E+05

|----+----o----+----o----+----o----+----| -1.23456E+04

Page 90: Programming With Fortran

AE6382

Format Specifiers – cont’d

G format code Syntax: Gw.d Print value of REAL variable using Fw.d format unless value is

too large or too small, in which case use Ew.d format. Ex:

G14.5 produces for the REAL value -1.23456789e+4:

When the number gets too big (or too small) for F, it is switched to an E format. Ex: the value -1.23456789e-18 becomes:

Note: the usefulness is more apparent when smaller field widths (w values) are specified for more compact output.

|----+----o----+----o----+----o----+----| -12345.67890

|----+----o----+----o----+----o----+----| -0.1234567E-19

Page 91: Programming With Fortran

AE6382

Other FORMAT Features

Forward slash, / Used to cause a new line to be started Does not need to be separated by commas

Repeat factor Format specifiers may be repeated by prepending a number to

specify the repeat factor Repeat groups are enclosed in ( ) Ex: 4F12.5 – same as F12.5,F12.5,F12.5,F12.5

Carriage control Line printers interpret the first character of each line as a

carriage control command and it is not printed.– 1 means start new page, – _(blank) means begin a new line, – + means over print current line

Common use: 1000 FORMAT(1X,4F12.4)

Page 92: Programming With Fortran

AE6382

Other I/O Features

The Fortran 77 method for associating a file with a unit is the OPEN statement

There is an extensive list of keywords that control OPEN, common keywords are ACCESS – SEQUENTIAL | DIRECT ACTION – READ | WRITE | READWRITE BLANK – NULL | ZERO ERR – label FILE – filename FORM – FORMATTED | UNFORMATTED IOSTAT – integer variable STATUS – OLD | NEW | SCRATCH | REPLACE | UNKNOWN UNIT – the unit number

OPEN(UNIT=7,STATUS=‘OLD’,FORM=‘UNFORMATTED’,FILE=‘DATA1.TXT’)

Page 93: Programming With Fortran

AE6382

Other I/O Features

ACCESS SEQUENTIAL – process each record in order (default for formatted io) DIRECT – access the file randomly (access record by number REC=)

BLANK – determines how blanks are processed by a format NULL – blanks are ignored – all blank field is zero ZERO – blanks are treated as zeros al BZ and BN format specifiers can be used

STATUS OLD – file must currently exist NEW – file cannot currently exist, it is created SCRATCH – an unnamed file that is created then destroyed on close REPLACE – if file exists then delete and re-create before opening UNKNOWN – if file does not exist create it otherwise open it

Page 94: Programming With Fortran

AE6382

Other I/O Features

The CLOSE statement will close a unit Keywords include

UNIT – unit to close STATUS – KEEP | DELETE ERR – label IOSTAT – integer variable

CLOSE(7)

CLOSE(7,STATUS=‘DELETE’)

Page 95: Programming With Fortran

AE6382

Other I/O Features

The BACKSPACE statement will position a sequential record back to the beginning of the previous record re-read a line

The ENDFILE statement will write an end of file marker then position a sequential file after it most useful with magnetic tape files

The INQUIRE statement will retrieve information about a file or logical unit

The REWIND statement will position a sequential file back to the beginning of the file

Page 96: Programming With Fortran

AE6382

Other I/O Features

A variation of the READ and WRITE statements is the internal read and write (77 only) they are identical to normal read/write statements except that

the UNIT is a CHARACTER variable earlier implementations of Fortran had statements such as

ENCODE (internal write) and DECODE (internal read)

CHARACTER*80 IMAGE

READ(IMAGE,9000) A,B 9000 FORMAT(2F8.2)

CHARACTER*80 IMAGE

WRITE(IMAGE,’(3E12.5)’) A,B,C

Page 97: Programming With Fortran

AE6382

Other I/O Features

A variation of the READ and WRITE statements is the internal read and write (77 only) they are identical to normal read/write statements except that

the UNIT is a CHARACTER variable earlier implementations of Fortran had statements such as

ENCODE (internal write) and DECODE (internal read)

CHARACTER*80 IMAGE

READ(IMAGE,9000) A,B 9000 FORMAT(2F8.2)

CHARACTER*80 IMAGE

WRITE(IMAGE,’(3E12.5)’) A,B,C

Page 98: Programming With Fortran

AE6382

Sub Programs

There are two types of Fortran sub-programs the subroutine the function

Functions return a value in an expression Subroutines are called as a stand-alone statement Sub-programs communicate with the caller using

arguments Common blocks are also used

reduce the flexibility of the routine faster, lower overhead

Page 99: Programming With Fortran

AE6382

Sub Programs

When a sub-program is declared, formal or dummy arguments are specified

Functions return a value

SUBROUTINE SUB1(A,B,I,J)

REAL J

DIMENSION A(5,5)

INTEGER B

REAL FUNCTION SINE(ANGLE)

SINE = …

RETURN

END

Page 100: Programming With Fortran

AE6382

Sub Programs

The formal arguments of a sub-program define the variables within that sub-program

When the sub-program is called, the variables used in the call are the actual arguments

The actual arguments are expected to match the formal arguments

Fortran before 90 does not check type For a function, the return value is placed in a variable of

the same name before return

Page 101: Programming With Fortran

AE6382

Sub Programs

Arguments in Fortran are passed by reference the address of the memory location is given to the sub-program changes made to the formal variable are reflected in the actual variable most other computer languages pass by value where a copy is made for

use by the sub-program For array variables

supplying only the name will pass the address of the start of the array with indices supplied, the address of that element is passed missing indices are assumed to be 1

DIMENSION A(5,5)

CALL SUB(A,A(3,2))

SUBROUTINE SUB(X,Y)

DIMENSION X(5,5)

REAL Y

END

Page 102: Programming With Fortran

AE6382

Sub Programs

When arrays are used the shape of the array must match in both the caller and the

called units the shape is the number of dimensions and extent of each

dimension, 5x5 a mis-match will generally result in incorrect calculations and

results

DIMENSION A(5,5)

CALL SUB(A)

SUBROUTINE SUB(X)

DIMENSION X(5,5)

END

Page 103: Programming With Fortran

AE6382

Sub Programs

A common sight for formal array declarations is the use of 1 as a dimension extent

This works only for the right-most index This works because the mapping from multi-dimensional

to one-dimensional form

DIMENSION A(5,5)

CALL SUB(A)

SUBROUTINE SUB(X)

DIMENSION X(5,1)

END

Page 104: Programming With Fortran

AE6382

Array Storage

Arrays in Fortran are stored in column major order C, C++, … store arrays in row major order, important to know if

calling sub-programs written in the other language

The array is allocated as a series of columns The left-most subscript varies fastest

For an array dimensioned as A(M,N). The mapping for element A(I,J) to the equivalent one-dimensional array is,

INDEX = (I - 1) * (J - 1)*M

Page 105: Programming With Fortran

AE6382

Array Storage program order

implicit none

integer i,j

integer a(5,5), b(25)

equivalence (a(1,1),b(1))

do i=1,5

do j=1,5

a(i,j) = i*100 + j

enddo

enddo

write(6,9000) ((a(i,j),j=1,5),i=1,5)

write(6,9010) b

write(6,9020) a

9000 format(/,'a(i,j): ',/,(5(1x,i4.4)))

9010 format(/,'b:',/,(15(1x,i4.4)))

9020 format(/,'a:',/,(5(1x,i4.4)))

end

a(i,j):

0101 0102 0103 0104 0105

0201 0202 0203 0204 0205

0301 0302 0303 0304 0305

0401 0402 0403 0404 0405

0501 0502 0503 0504 0505

b:

0101 0201 0301 0401 0501 0102 0202 0302 0402 0502 0103 0203 0303 0403 0503

0104 0204 0304 0404 0504 0105 0205 0305 0405 0505

a:

0101 0201 0301 0401 0501

0102 0202 0302 0402 0502

0103 0203 0303 0403 0503

0104 0204 0304 0404 0504

0105 0205 0305 0405 0505

Page 106: Programming With Fortran

AE6382

Sub Programs

Arguments can be used to define the shape of the array

This only works for formal arguments Frequently used with the PARAMETER statement

INTEGER A(5,5)

CALL SUB(A,5,5)

END

SUBROUTINE SUB(J,IROW,ICOL)

DIMENSION J(IROW,ICOL)

END

Page 107: Programming With Fortran

AE6382

Sub Programs program main_add

implicit none

c

c define the largest matrix allowed

integer MAXROW,MAXCOL

parameter (MAXROW=9,MAXCOL=9)

c

c allocate memory for the matricies

real a(MAXROW,MAXCOL)

real b,c

dimension b(MAXROW,MAXCOL),c(MAXROW,MAXCOL)

c

c local memory

integer i,j,m,n

character*80 line

c

c read the first line of the file, the title

read(5,'(a80)') line

c

c read the size of the matrices to be input

read(5,*) m,n

write(6,*) 'M=',m,', N=',n

c

c read the a matrix (using old-style do loop)

do 10 i=1,m

read(5,8000) (a(i,j),j=1,n)

write(6,*)i,(a(i,j),j=1,n)

10 continue

c

c read the b matrix (using new-style do loop)

do i=1,m

read(5,8010) (b(i,j),j=1,n)

write(6,*)i,(b(i,j),j=1,n)

enddo

c

c call the subroutine to add the matrices, result in c

call add(a,b,c,MAXROW,m,MAXCOL,n)

c

c write the result (use dual implied do loops)

write(6,*)'Output 1'

write(6,9000) ((c(i,j),j=1,n),i=1,m)

c

c write the result (use explicit do loop for rows)

c (use implied do loop for columns)

write(6,*) 'Output 2'

do 20 i=1,m

write(6,9000) (c(i,j),j=1,n)

20 continue

c

c formats for input and output

8000 format(5f10.2)

8010 format(bz,5f10.2)

9000 format(10f14.4)

end

Page 108: Programming With Fortran

AE6382

Sub Programsc

c define the subroutine to perform the matrix addition

c this subroutine takes 3 matricies a,b,c

c c = a + c (matrix addition)

c a, b, and c are declared in the calling program to have

c dimension (mmax,nmax) (all the same)

c the actual matrix contained is (m,n)

c

subroutine add(a,b,c,mmax,m,nmax,n)

implicit none

c

c declare type of other arguments

integer mmax,m,nmax,n

c

c "dynamic" dimensioning of the matrices

real a(mmax,nmax)

real b(mmax,nmax)

c

c the right-most dimension can always be specified as 1

c see the 1-d conversion formula as to why

c not good practice but common in code

real c(mmax,1)

c local variables

integer i,j

c

c loop over each element and add

do i=1,m

do j=1,n

c(i,j)=a(i,j)+b(i,j)

enddo

enddo

return

end

Page 109: Programming With Fortran

AE6382

Sub Programs

A program using common blocks to communicate The INCLUDE statement is used to ensure that all the

parts of the program use the same definitions A makefile is shown

it checks the current state of all the source files if common.f is changed it will ensure that the other files that

reference it are re-compile to reflect changes sample is the first target and therefore the default

Page 110: Programming With Fortran

AE6382

Sub ProgramsPART1.F

program sample

include 'common.f‘

write(*,*) 'a=',a,', b=',b,', c=',c

call modify

write(*,*) 'a=',a,', b=',b,', c=',c

end

PART2.F

block data

include 'common.f‘

data a,b,c/7,42,70/

end

PART3.F

subroutine modify

include 'common.f‘

integer total

total = a + b + c

write(*,*) "Total=",total

a = a / 2

b = b / 2

c = c / 2

return

end

COMMON.F

common/test/a,b,c

integer a,b,c

MAKEFILE

sample: part1.o part2.o part3.o

g77 -o sample part1.o part2.o part3.o

part1.o: part1.f common.f

g77 -c part1.f

part2.o: part2.f common.f

g77 -c part2.f

part3.o: part3.f common.f

g77 -c part3.f

Page 111: Programming With Fortran

AE6382

Statement Functions

The statement function is a special case of the function It is defined and used in the calling program

It is a macro for a simple computation It is defined in the declarations It has been removed as of Fortran 95

F(X,Y) = X**2 + Y

A = 3.245 * F(4.3,B) - C

END

Page 112: Programming With Fortran

AE6382

Fortran Books

There are some freely downloadable Fortran 77 books Professional Programmer’s Guide to Fortran 77

http://www.star.le.ac.uk/~cgp/fortran.html PDF, HTML, and TeX versions are available also on tsquare under resources

Interactive Fortran 77: A Hands On Approach http://www.kcl.ac.uk/kis/support/cc/fortran/f77book.pdf can be downloaded from above

Page 113: Programming With Fortran

AE6382

Not Fortran

#include <stdio.h>

main(t,_,a)

char *a;

{

return!0<t?t<3?main(-79,-13,a+main(-87,1-_,main(-86,0,a+1)+a)):

1,t<_?main(t+1,_,a):3,main(-94,-27+t,a)&&t==2?_<13?

main(2,_+1,"%s %d %d\n"):9:16:t<0?t<-72?main(_,t,

"@n'+,#'/*{}w+/w#cdnr/+,{}r/*de}+,/*{*+,/w{%+,/w#q#n+,/#{l+,/n{n+,/+#n+,/#\

;#q#n+,/+k#;*+,/'r :'d*'3,}{w+K w'K:'+}e#';dq#'l \

q#'+d'K#!/+k#;q#'r}eKK#}w'r}eKK{nl]'/#;#q#n'){)#}w'){){nl]'/+#n';d}rw' i;# \

){nl]!/n{n#'; r{#w'r nc{nl]'/#{l,+'K {rw' iK{;[{nl]'/w#q#n'wk nw' \

iwk{KK{nl]!/w{%'l##w#' i; :{nl]'/*{q#'ld;r'}{nlwb!/*de}'c \

;;{nl'-{}rw]'/+,}##'*}#nc,',#nw]'/+kd'+e}+;#'rdq#w! nr'/ ') }+}{rl#'{n' ')# \

}'+}##(!!/")

:t<-50?_==*a?putchar(31[a]):main(-65,_,a+1):main((*a=='/')+t,_,a+1)

:0<t?main(2,2,"%s"):*a=='/'||main(0,main(-61,*a,

"!ek;dc i@bK'(q)-[w]*%n+r3#l,{}:\nuwloca-O;m .vpbks,fxntdCeghiry"),a+1);

}

Page 114: Programming With Fortran

AE6382