introduction to fortran 90 si liu july 19, 2010 ncar/cisl/osd/hss consulting services group

72
Introduction to Fortran 90 Si Liu Si Liu July 19, 2010 July 19, 2010 NCAR/CISL/OSD/HSS NCAR/CISL/OSD/HSS Consulting Services Group Consulting Services Group

Upload: brianna-knight

Post on 22-Dec-2015

226 views

Category:

Documents


4 download

TRANSCRIPT

Page 1: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Introduction to Fortran 90

Si LiuSi Liu

July 19, 2010July 19, 2010NCAR/CISL/OSD/HSSNCAR/CISL/OSD/HSS

Consulting Services GroupConsulting Services Group

Page 2: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Syllabus

IntroductionBasic syntaxArraysControl structuresScopesI/O

Page 3: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Introduction

HistoryObjectivesMajor new featuresOther new featuresAvailability of compilers

Page 4: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

History of FortranFORTRAN is an acronym for FORmula TRANslation

IBM Fortran (1957)Fortran 66 standard (1966)Fortran 77 standard (1978)Fortran 90 standard (1991)Fortran 95 standard (1996)Fortran 2003 standardFortran 2008 standard

Page 5: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Objective

Language evolutionObsolescent features

Standardize vendor extensions

Portability

Modernize the language• Ease-of-use improvements through new features such as

free source form and derived types• Space conservation of a program with dynamic memory

allocation• Modularization through defining collections called modules• Numerical portability through selected precision

Page 6: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Objective, continued

Provide data parallel capabilityParallel array operations for better use of vector and parallel processors

Compatibility with Fortran 77 Fortran 77 is a subset of Fortran 90

Improve safety Reduce risk of errors in standard code

Standard conformanceCompiler must report non standard code and obsolescent features

Page 7: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Major new features

Array processing Dynamic memory allocation ModulesProcedures:

• Optional/Keyword Parameters• Internal Procedures• Recursive Procedures

Pointers

Page 8: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Other new features

Free-format source codeSpecifications/Implicit noneParameterized data types (KIND)Derived types Operator overloadingNew control structuresNew intrinsic functionsNew I/O features

Page 9: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Available Fortran 90 compilers gfortran — the GNU Fortran compiler Cray CF90 DEC Fortran 90 EPC Fortran 90 IBM XLF Lahey LF90 Microway NA Software F90+ NAG f90 Pacific Sierra VAST-90 Parasoft Salford FTN90

Page 10: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

First Fortran programSyntax Example1 helloworld

syntax_ex1.f90

PROGRAM HelloWorld

! Hello World in Fortran 90 and 95

WRITE(*,*) "Hello World!"

END PROGRAM

Compile and run

gfortran syntax_ex1.f90 -o syntax_ex1.o

./syntax_ex1.o

Page 11: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Source formLines up to 132 charactersLowercase letters permittedNames up to 31 characters (including underscore)Semicolon to separate multiple statements on one

lineComments may follow exclamation (!)Ampersand (&) is a continuation symbolCharacter set includes + < > ; ! ? % - “ &New relational operators: ‘<’, ‘<=’, ‘==’,’/=‘,’>=‘,’>’

Page 12: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Source formfree_source_form.f90

PROGRAM free_source_form

! Long names with underscores

! No special columns

IMPLICIT NONE

! upper and lower case letters

REAL :: tx, ty, tz ! trailing comment

! Multiple statements per line

tx = 1.0; ty = 2.0; tz = tx * ty;

! Continuation on line to be continued

PRINT *, &

tx, ty, tz• END PROGRAM free_source_form

Page 13: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Specifications

type [[,attribute]... ::] entity list

type can be INTEGER, REAL, COMPLEX,

LOGICAL, CHARACTER or TYPE with optional kind value:

• INTEGER [(KIND=] kind-value)]• CHARACTER ([actual parameter list])

([LEN=] len-value and/or [KIND=] kind-value)• TYPE (type name)

Page 14: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Specifications, continued

type [[,attribute]... ::] entity list

attribute can bePARAMETER, PUBLIC, PRIVATE,

ALLOCATABLE, POINTER, TARGET,

INTENT(inout), DIMENSION (extent-list),

OPTIONAL, SAVE, EXTERNAL,

INTRINSIC

Can initialize variables in specifications

Page 15: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Specifications

! Integer variables:

INTEGER :: ia, ib! Parameters:

INTEGER, PARAMETER :: n=100, m=1000! Initialization of variables:

REAL :: a = 2.61828, b = 3.14159 ! Logical variable

LOGICAL :: E=.False.

Page 16: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Specifications

! Character variable of length 20:

CHARACTER (LEN = 20) :: ch! Integer array with negative lower bound:

INTEGER, DIMENSION(-3:5, 7) :: ia! Integer array using default dimension:

INTEGER,DIMENSION(-3:5, 7) :: ib, ic(5, 5)

Page 17: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

IMPLICIT NONE

In Fortran 77, implicit typing permitted use of undeclared variables. This has been the cause of many programming errors.

IMPLICIT NONE forces you to declare the type of all variables, arrays, and functions.

IMPLICIT NONE may be preceded in a program unit only by USE and FORMAT.

It is recommended to include this statement in all program units.

Page 18: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Kind Values

5 intrinsic types: REAL, INTEGER, COMPLEX, CHARACTER, LOGICAL

Each type has an associated non negative integer value called the KIND type parameter

Useful feature for writing portable code requiring specified precision

A processor must support at least 2 kinds for REAL and COMPLEX, and 1 for INTEGER, LOGICAL and CHARACTER

Many intrinsics for enquiring about and setting kind values

Page 19: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Kind Values

INTEGER(8) :: IREAL(KIND=4) :: FCHARACTER(10) :: C

INTEGER :: IK=SELECTED_INT_KIND(9)INTEGER :: IR=SELECTED_REAL_KIND(3,10)

Page 20: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Kind values: INTEGER

INTEGER (KIND = wp) :: ia ! or

INTEGER(wp) :: ia

Integers usually have 16, 32, or 64 bit 16 bit integer normally permits -32768 < i < 32767 Kind values are system dependent

• An 8 byte integer variable usually has kind value 8 or 2• A 4 byte integer variable usually has kind value 4 or 1

Page 21: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Kind values: INTEGER, continued

To declare integer in system independent way, specify kind value associated with range of integers required:

INTEGER, PARAMETER :: &

i8 =SELECTED_INT_KIND(8)

INTEGER (KIND = i8) :: ia, ib, ic

ia, ib and ic can have values between -108 and +108 at least (if permitted by processor).

Page 22: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Kind values: REAL

REAL (KIND = wp) :: ra ! or

REAL(wp) :: ra

Declare a real variable, ra, whose precision is determined by the value of the kind parameter, wp

Kind values are system dependent• An 8 byte (64 bit) real variable usually has kind value 8 or 2.• A 4 byte (32 bit) real variable usually has kind value 4 or 1.

Literal constants set with kind value: const = 1.0_wp

Page 23: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Kind values: REAL,continued

To declare real in system independent way, specify kind value associated with precision and exponent range required:

INTEGER, PARAMETER :: &

i10 = SELECTED_REAL_KIND(10, 200)

REAL (KIND = i10) :: a, b, c

a, b and c have at least 10 decimal digits of precision and the exponent range 200.

Page 24: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Kind values: Intrinsics

INTEGER, PARAMETER :: &

i8 = SELECTED_INT_KIND(8)

INTEGER (KIND = i8) :: ia

PRINT *, KIND(ia)

This will print the kind value of ia.

INTEGER, PARAMETER :: &

i10 = SELECTED_REAL_KIND(10, 200)

REAL (KIND = i10) :: a

PRINT *, RANGE(a), PRECISION(a), KIND(a)

This will print the exponent range, the decimal digits of precision and the kind value of a.

Page 25: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Syntax Example 2 syntax_ex2.f90

Program Triangle

implicit none

real :: a, b, c, Area

print *, 'Welcome, please enter the & &lengths of the 3 sides.'

read *, a, b, c print *, 'Triangle''s area: ', Area(a,b,c)

end program Triangle

Page 26: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Syntax Example 2 , continued

Function Area(x,y,z)

implicit none

! function type

real :: Area

real, intent (in) :: x, y, z

real :: theta, height

theta = acos((x**2+y**2-z**2)/(2.0*x*y))

height = x*sin(theta)

Area = 0.5*y*height

end function Area

Page 27: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Types exercise 1

Types exercise 1 solutions

Page 28: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Derived Types (structures)

Defined by userCan include different intrinsic types and

other derived typesComponents accessed using percent (%)Only assignment operator (=) is defined

for derived typesCan (re)define operators

Page 29: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Derived Types Define the form of derived type

TYPE vreg

CHARACTER (LEN = 1) :: model

INTEGER :: number

CHARACTER (LEN = 3) :: place

END TYPE vreg

Create the structures of that typeTYPE (vreg) :: mycar1, mycar2

Assigned by a derived type constantmycar1 = vreg(’L’, 240, ’VPX’)

Use % to select a component of that typemycar2%model = ’R’

Page 30: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Derived Types

Arrays of derived types:TYPE (vreg), DIMENSION (n) :: mycars

Derived type including derived type:TYPE household

CHARACTER (LEN = 30) :: name

CHARACTER (LEN = 50) :: address

TYPE (vreg) :: car

END TYPE household

TYPE (household) :: myhouse

myhouse%car%model = ’R’

Page 31: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Control Structures

Three block constructs

• IF

• DO and DO WHILE

• CASE All can be nested All may have construct names to help

readability or to increase flexibility

Page 32: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Control structure: IF[name:]IF (logical expression) THEN

block

[ELSE IF (logical expression) THEN [name] block]...

[ELSE [name]

block]

END IF [name]

Page 33: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: IF

IF (i < 0) THEN

CALL negative

ELSE IF (i == 0) THEN

CALL zero

ELSE selection

CALL positive

END IF

Page 34: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Control Structure: Do

[name:] DO [control clause]

block

END DO [name]

Control clause may be:• an iteration control clause

count = initial, final [,inc]• a WHILE control clause

WHILE (logical expression)• or nothing (no control clause at all)

Page 35: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: DO

Iteration control clause:

rows: DO i = 1, n

cols: DO j = 1, m

a(i, j) = i + j

END DO cols

END DO rows

Page 36: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: DO

WHILE control clause:

true: DO WHILE (i <= 100)

...

body of loop

...

END DO true

Page 37: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Use of EXIT and CYCLE

exit from loop with EXITtransfer to END DO with CYCLEEXIT and CYCLE apply to inner loop by

default, but can refer to specific, named loop

Page 38: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Do outer: DO i = 1, n

middle: DO j = 1, m

inner: DO k = 1, l

IF (a(i,j,k) < 0.0) EXIT outer ! leave loops

IF (j == 5) CYCLE middle ! set j = 6

IF (i == 5) CYCLE ! skip rest of inner

...

END DO inner

END DO middle

END DO outer

Page 39: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: DO

No control clause:

DO

READ (*, *) x

IF (x < 0) EXIT

y = SQRT(x)

...

END DO

Notice that this form can have the same effect as a DO WHILE loop.

Page 40: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Control Structures: CASE

Structured way of selecting different options, dependent on value of single Expression

Replacement for• computed GOTO• or IF ... THEN ... ELSE IF ... END IF

constructs

Page 41: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Control Structure: CASE

General form:

[name:] SELECT CASE (expression)

[CASE (selector) [name]

block]

...

END SELECT [name]

Page 42: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Control Structure: CASE

expression - character, logical or integerselector - DEFAULT, or one or more

values of same type as expression:• single value• range of values separated by : (character or

integer only), upper or lower value may be absent

• list of values or ranges

Page 43: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: CASE

hat: SELECT CASE (ch)

CASE (’C’, ’D’, ’G’:’M’)

color = ’red’

CASE (’X’)

color = ’green’

CASE DEFAULT

color = ’blue’

END SELECT hat

Page 44: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Arrays

TerminologySpecificationsArray constructorsArray assignmentArray sections

Page 45: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Arrays, continued

Whole array operationsWHERE statement and constructAllocatable arraysAssumed shape arraysArray intrinsic procedures

Page 46: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Specifications

type [[,DIMENSION (extent-list)] [,attribute]... ::] entity-list

where: type - INTRINSIC or derived type DIMENSION - Optional, but required to define default dimensions (extent-list) - Gives array dimension:

• Integer constant• integer expression using dummy arguments or constants.• if array is allocatable or assumed shape.

attribute - as given earlier entity-list - list of array names optionally with dimensions and initial values.

REAL, DIMENSION(-3:4, 7) :: ra, rb

INTEGER, DIMENSION (3) :: ia = (/ 1, 2, 3 /), ib = (/ (i, i = 1, 3) /)

Page 47: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Terminology

Rank:Number of dimensions Extent:Number of elements in a dimension Shape:Vector of extents Size:Product of extents Conformance: Same shape

REAL, DIMENSION :: a(-3:4, 7)

REAL, DIMENSION :: b(8, 2:8)

REAL, DIMENSION :: d(8, 1:8)

Page 48: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Array Constructor

Specify the value of an array by listing its elements

p = (/ 2, 3, 5, 7, 11, 13, 17 /)

DATA

REAL RR(6)

DATA RR /6*0/

Reshape

REAL, DIMENSION (3, 2) :: ra

ra = RESHAPE( (/ ((i + j, i = 1, 3), j = 1, 2) /), &

SHAPE = (/ 3, 2 /) )

Page 49: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Array sections

A sub-array, called a section, of an array may be referenced by specifying a range of subscripts, either:

A simple subscript• a (2, 3) ! single array element

A subscript triplet• [lower bound]:[upper bound] [:stride]

a(1:3,2:4)• defaults to declared bounds and stride 1

A vector subscript

iv =(/1,3,5/)

rb=ra(iv)

Page 50: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Array assignment

Operands must be conformable

REAL, DIMENSION (5, 5) :: ra, rb, rc

INTEGER :: id

...

ra = rb + rc * id ! Shape(/ 5, 5 /)

ra(3:5, 3:4) = rb(1::2, 3:5:2) + rc(1:3, 1:2)

! Shape(/ 3, 2 /)

ra(:, 1) = rb(:, 1) + rb(:, 2) + rb(:, 3)

! Shape(/ 5 /)

Page 51: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Whole array operations

Arrays for whole array operation must be conformable

Evaluate element by element, i.e., expressions evaluated before assignment

Scalars broadcastFunctions may be array valued

Page 52: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Whole array operations, continued

Fortran 77:

REAL a(20), b(20), c(20)

DO 10 i = 1, 20

a(i) = 0.0

10 CONTINUE

DO 20 i = 1, 20

a(i) = a(i) / 3.1 + b(i) *SQRT(c(i))

20 CONTINUE

Fortran 90:

REAL, DIMENSION (20) :: a, b, c

...

a = 0.0

...

a = a / 3.1 + b * SQRT(c)

...

Page 53: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Array examples

Array example 1Array example 1 - Fortran 90 solution

Array example 2Array example 2 - Fortran 90 solution

Page 54: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Where statementForm:

WHERE (logical-array-expr)

array-assignments

ELSEWHERE

array-assignments

END WHERE

REAL DIMENSION (5, 5) :: ra, rb

WHERE (rb > 0.0)

ra = ra / rb

ELSEWHERE

ra = 0.0

END WHERE

Another example: where_ex.f90

Page 55: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Allocatable arrays A deferred shape array which is declared with the ALLOCATABLE attribute ALLOCATE(allocate_object_list [, STAT= status]) DEALLOCATE(allocate_obj_list [, STAT= status]) When STAT= is present, status = 0 (success) or status > 0 (error). When

STAT= is not present and an error occurs, the program execution aborts

REAL, DIMENSION (:, :), ALLOCATABLE :: ra

INTEGER :: status

READ (*, *) nsize1, nsize2

ALLOCATE (ra(nsize1, nsize2), STAT = status)

IF (status > 0) STOP ’Fail to allocate meomry’

...

IF (ALLOCATED(ra)) DEALLOCATE (ra)

...

Page 56: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Allocatable array

Array example 3 - allocatable array

Page 57: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Scopes

The scope of a named entity or label is the set of non-overlapping scoping units where that name or label may be used unambiguously.

A scoping unit is one of the following: a derived type definition, a procedure interface body, excluding any derived-type

definitions and interface bodies contained within it, a program unit or an internal procedure, excluding

derived-type definitions, interface bodies, and subprograms contained within it.

Page 58: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Scopes: Labels and names The scope of a label is a main program or a procedure,

excluding any internal procedures contained within it. Entities declared in different scoping unit are always

different. Within a scoping unit, each named entity must have a

distinct name, with the exception of generic names of procedures.

The names of program units are global, so each must distinct from the others and from any of the local entities of the program unit.

The scope of a name declared in a module extends to any program units that USE the module.

Page 59: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Scope example

scope_ex1.f90

Page 60: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

I/O

Page 61: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Namelist

Gather set of variables into group to simplify I/OGeneral form of NAMELIST statement:

NAMELIST /namelist-group-name/ variable-list

Use namelist-group-name as format

instead of io-list on READ and WRITEInput record has specific format:

&namelist-group-name var2=x, var1=y, var3=z/

Variables optional and order unimportant

Page 62: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Namelist

...

INTEGER :: size = 2

CHARACTER (LEN = 4) :: &

color(3) = (/ ’ red’, ’pink’, ’blue’ /)

NAMELIST /clothes/ size, color

WRITE(*, NML = clothes)

...

outputs:

&CLOTHES

SIZE= 2,

COLOR= red,pink,blue, /

Page 63: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Formatted I/OPROGRAM TEST_IO_1

IMPLICIT NONE

INTEGER :: I,J

REAL:: A,B

READ *, I,J

READ *,A,B

PRINT *,I,J

PRINT *,A,B

END PROGRAM TEST_IO_1

Page 64: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Formatted I/O

PROGRAM TEST_IO_2

IMPLICIT NONE

REAL A,B,C

WRITE(*,*)"Please enter 3 real numbers:"

READ(*,10)A,B,C

WRITE(*,*)"These 3 real numbers are:"

PRINT 20,A,B,C

10 FORMAT(3(F6.2,1X))

20 FORMAT(1X,'A= ',F6.2,' B= ',F6.2,' C= ', F6.2)

END PROGRAM TEST_IO_2

Page 65: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example

INTEGER :: rec_len

...

INQUIRE (IOLENGTH = rec_len) name, title, &

age, address, tel

...

OPEN (UNIT = 1, FILE = ’test’, RECL = rec_len, &

FORM = ’UNFORMATTED’)

...

WRITE(1) name, title, age, address, tel

Page 66: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

INQUIRE by I/O list

INQUIRE (IOLENGTH=length) output-list

To determine the length of an unformatted output item list

May be used as value of RECL specifier in subsequent OPEN statement

Page 67: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Example: Unformatted I/O• Unformatted direct access I/O most efficient, but not human-

readable

• You must open a file with the format=‘unformatted’ attribute in order to write data to it. Example:

See io_ex4.f90 for detail

integer I, iu ! iu is the unit number for your file, foo.out

real X :: 7.0

open (iu, form='unformatted',access='direct’,file='foo.out')

do iter= 1,4

write (iu, rec=iter, X)

end do

close (iu)

Page 68: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Resources

CSG will provide Fortran 90 support.Walk-in, mail, phone, etc. (ML suite 42).

CSG-wiki –Fortran90 tutorial

• https://wiki.ucar.edu/display/csg/Introduction+to+Fortran90

Page 69: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Recommended text

Full text on Books 24x7 in NCAR Library

Page 70: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

References

Fortran 90: A Conversion Course for Fortran 77 Programmers OHP Overviews

F Lin, S Ramsden, M A Pettipher, J M Brooke, G S Noland, Manchester and North HPC T&EC

An introduction to Fortran 90 and Fortran 90 for programmers

A Marshall, University of Liverpool

Fortran 90 for Fortran 77 Programmers

Clive page, University of Leicester

Page 71: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group

Acknowledgments

• Siddhartha Ghosh

• Davide Del Vento

• Rory Kelly

• Dick Valent

• Other colleagues from CISL

• Manchester and North HPC T&EC

• University of Liverpool for examples

Page 72: Introduction to Fortran 90 Si Liu July 19, 2010 NCAR/CISL/OSD/HSS Consulting Services Group