Sie sind auf Seite 1von 71

Preparation

Log in to mirage
o ssh l username mirage[0-4].ucar.edu o Use CryptoCard or Yubikey

Obtain the example source code


o cp r /glade/home/siliu/f90_1 your-own-directory

Slides and handouts are available at:


www2.cisl.ucar.edu/training/CSG_winter_2011

In case you are not working on mirage:


o download the tar ball
o tar xf f90_1.tar

Introduction to Fortran 90
Consulting Services Group Si Liu (Presenter) Feb 14, 2011 NCAR/CISL/OSD/USS

Syllabus

Introduction Basic syntax Arrays Control structures Basic I/O

Introduction
History Objectives Major new features Other new features Availability of compilers

History of Fortran
FORTRAN 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 standard (2004) Fortran 2008 standard (2010)

Objectives
Language evolution
Obsolescent 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

Objectives, continued
Provide data parallel capability
Parallel 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 conformance
Compiler must report non standard code and obsolescent features

Major new features


Array processing Dynamic memory allocation Modules Procedures:
Optional/Keyword Parameters Internal Procedures Recursive Procedures

Pointers

Other new features


Free-format source code Specifications/Implicit none Parameterized data types (KIND) Derived types Operator overloading New control structures New intrinsic functions New I/O features

Available Fortran 90 compilers


Intel Fortran Compiler: Ifort IBM XL Fortran Compiler: XLF GNU Fortran compiler: gfortran PGI Fortran Compiler: pgf90 Cray CF90 EKOPATH (PathScale) DEC Fortran 90 EPC Fortran 90 Microway NA Software F90+ Pacific Sierra VAST-90

First Fortran program


Syntax Example1: syntax_ex1.f90
PROGRAM HelloWorld ! Hello World in Fortran 90 and 95 WRITE(*,*) "Hello World!" END PROGRAM
Compile and run ifort syntax_example1.f90 -o syntax_example1.exe ./syntax_ex1.exe

Free source form


Lines up to 132 characters Lowercase letters permitted Names up to 31 characters (including underscore) Semicolon to separate multiple statements on one line Comments may follow exclamation (!) Ampersand (&) is a continuation symbol Character set includes + < > ; ! ? % - & New relational operators: <, <=, ==,/=,>=,>

Example: Source form


free_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

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)

Specifications, continued
type [[,attribute]... ::] entity list attribute can be
PARAMETER, ALLOCATABLE, INTENT(inout), OPTIONAL, INTRINSIC PUBLIC, PRIVATE, POINTER, TARGET, DIMENSION (extent-list), SAVE, EXTERNAL,

Can initialize variables in specifications

Example: Specifications spcifiacation.f90


! Integer variables: INTEGER :: ia, ib ! Parameters: INTEGER, PARAMETER :: n=100, m=1000 ! Initialization of variables: REAL :: a = 2.61828, b = 3.14159 !Logical variables LOGICAL :: E=.False. ! Character variable of length 20: CHARACTER (LEN = 20) :: ch

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.

Intrinsic Logical Operations

Relational Operators
.GT. .GE. .LE. .LT. .NE. .EQ. > >= <= < /= ==

.NOT. .AND. .OR. .EQV. .NEQV.

Numeric Operations
**: exponentiation * and / : multiply and divide + and - : plus and minus

Character operations string1.f90


Intrinsic Character Operations substring Character(Len=20) :: ch Ch=specification ch(1:1) is s ch(10:13) us tion Intrinsic Character Operations Concatenation Character(Len=5), Parameter :: s1 = & abcde Character(Len=20) :: s2=s1//fg PRINT *, hello //world //again PRINT *, s2

ch(1) error

Kind Values
5 intrinsic types: REAL, INTEGER, COMPLEX, CHARACTER, LOGICAL Each type has an associated non negative integer value called the KIND type parameter 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 Useful feature for writing portable code requiring specified precision

Example: Kind Values


INTEGER(8) :: I REAL(KIND=4) :: F

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

Kind values: INTEGER


INTEGER (KIND = wp) :: ia INTEGER(wp) :: ia ia=3.0_wp ! or ! or

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

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).

Kind example: kind1.f90


INTEGER, PARAMETER :: k2=SELECTED_INT_KIND(2) INTEGER, PARAMETER :: k4=SELECTED_INT_KIND(4) INTEGER(kind=k2) :: i2 INTEGER(kind=k4) :: i4 print *,"k2= ",k2 print *,"k4= ",k4

print *,"huge(i2)= ", huge(i2) print *,"huge(i4)= ", huge(i4)

Kind values: REAL


REAL (KIND = wp) :: ra REAL(wp) :: ra ra= 3.14_wp ! or ! or

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.

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.

Kind example: kind2.f90


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.

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

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

Derived Types (structures)


Defined by user Can include different intrinsic types and other derived types Components accessed using percent (%) Only assignment operator (=) is defined for derived types Can (re)define operators

Example: Derived Types


Define the form of derived type
TYPE acar CHARACTER (LEN = 10) :: model INTEGER :: year CHARACTER (LEN = 3) :: style END TYPE acar

Create the structures of that type


TYPE (acar) :: mycar1, mycar2

Assigned by a derived type constant


mycar1 = acar(Nissan, 2000, ABC)

Use % to select a component of that type


mycar2%model = Mazda

Example: Derived Types


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

Derived type including derived type:


TYPE household CHARACTER (LEN = 30) :: name CHARACTER (LEN = 50) :: address TYPE (acar) :: mycar END TYPE household

TYPE (household) :: myhouse myhouse%mycar%model = Lexus

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

Control structure: IF
[name:]IF (logical expression) THEN block [ELSE IF (logical expression) THEN [name] block]... [ELSE [name] block] END IF [name]

Example: IF
IF (i < 0) THEN CALL negative ELSE IF (i == 0) THEN CALL zero ELSE selection CALL positive END IF see if_ex1.f90

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)

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

Example: DO
WHILE control clause: true: DO WHILE (i <= 100) ... body of loop ... END DO true

Use of EXIT and CYCLE


exit from loop with EXIT transfer to END DO with CYCLE EXIT and CYCLE apply to inner loop by default, but can refer to specific, named loop

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 IF (j == 5) CYCLE middle IF (i == 5) CYCLE ... END DO inner END DO middle END DO outer

! leave loops ! set j = 6 ! skip rest of inner

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.

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

Control Structure: CASE


General form: [name:] SELECT CASE (expression) [CASE (selector) [name] block] ... END SELECT [name]

Control Structure: CASE


expression - character, logical or integer selector - 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

Example: CASE
hat: SELECT CASE (ch) CASE (C, D, G:M) color = red CASE (X) color = green CASE DEFAULT color = blue END SELECT hat

Array

Arrays
Terminology Specifications Array constructors Array assignment Array sections

Arrays, continued
Whole array operations WHERE statement and construct Allocatable arrays Array intrinsic procedures

Terminology
Column majored 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)

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 :, 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) /)

Array Constructor
Specify the value of an array by listing its elements p = (/ 2, 3, 5, 7, 11, 13, 17 /) DATA DATA SS /6*0/ Reshape REAL, DIMENSION (3, 2) :: ra ra = RESHAPE( (/ ((i + j, i = 1, 3), j = 1, 2) /), & SHAPE = (/ 3, 2 /) )

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)

Whole array operations


Arrays for whole array operation must be conformable Evaluate element by element, i.e., expressions evaluated before assignment Scalars broadcast Functions may be array valued

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) ...

Array examples

Use fixed or FI option to compile the code in fixed format Array example 1 Array example 2

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 /)

Array Intrinsic Functions


ALL(mask, dim) .true. if all elements are true ANY(mask, dim) .true. if any elements are true COUNT(mask, dim) Number of true elements SUM(array, dim, mask) Sum of elements x PRODUCT(array, dim, mask) Product of elements MAXVAL(array, dim, mask) Maximum value in array MINVAL(array, dim, mask) Minimum value in array DOT_PRODUCT(va, vb) Dot product of two vectors MATMUL(mata, matb) Matrix multiplication (or matrix X vector) TRANSPOSE(matrix) Transpose of 2-d array MAXLOC(array, mask) Location of maximum element MINLOC(array, mask) Location of minimum element

Where statement
Form: 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

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
...

array_ex3.f90
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)

Basic I/O

Namelist
Gather set of variables into group to simplify I/O General form of NAMELIST statement:
NAMELIST /namelist-group-name/ variable-list

Use namelist-group-name as format instead of io-list on READ and WRITE Input record has specific format:
&namelist-group-name var2=x, var1=y, var3=z

Variables optional and order unimportant

Example: Namelist see example: nml_ex.f90


... INTEGER :: size = 2 CHARACTER (LEN = 5) :: & color(3) = (/ red , pink , blue /) NAMELIST /clothes/ size, color WRITE(*, NML = clothes) ... outputs: &CLOTHES SIZE = 2, COLOR = red pink blue /

Example: Formatted I/O


see example: io_ex1.f90

INTEGER :: I,J REAL:: A,B PRINT *,"Enter two integers, I and J:" READ *, I,J PRINT *,"Enter two Reals, A and B:" READ *,A,B

PRINT *,"I= ",I,"J= ",J PRINT *,"A= ",A,"B= ",B

Example: Formatted I/O


see example: io_ex2.f90

DO I=-3,3 WRITE(*,100) I END DO 100 FORMAT(1X,5I5) WRITE(*,200) (J,J=-3,3) 200 FORMAT(1X,7I5)

Example: Formatted I/O


see example: io_ex3.f90
Fw.d w: the number of positions to be used d: the number of digits to the right of the decimal point PROGRAM io_ex3 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('A= ',F6.2,' B= ',F6.2,' C= ', F6.2) END PROGRAM io_ex3

Recommended text

Full text on Books 24x7 in NCAR Library

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

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

Resources
Forums for the Fortran 90 course http://sea.ucar.edu/forum
CSG will provide Fortran 90 support.
Walk-in: ML suite 51/55 Phone: (303)-497-1200 Email: cislhelp@ucar.edu

Das könnte Ihnen auch gefallen