an introduction to fortran -...

43
An Introduction to Fortran Sylvia Pl¨ ockinger March 10, 2011 Sylvia Pl¨ ockinger () An Introduction to Fortran March 10, 2011 1 / 43

Upload: trinhthuan

Post on 10-Jul-2018

295 views

Category:

Documents


9 download

TRANSCRIPT

Page 1: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

An Introduction to Fortran

Sylvia Plockinger

March 10, 2011

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 1 / 43

Page 2: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

General Information

Find this file on:

http://homepage.univie.ac.at/nigel.mitchell/NumPrac/

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 2 / 43

Page 3: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Outline

1 Literature

2 History

3 Fortran 90

4 Declaration Part

5 Execution Part

6 Modules

7 Back to F77

8 Gnuplot

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 3 / 43

Page 4: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Literature

Literature in the Astronomy Library:

“Fortran 90/95 for Scientists and Engineers”, Stephen J. Chapman

“Introduction to Programming with Fortran”, I. Chivers, J. Sleightholme

“Fortran for the ’90s”, Stacey L. Edgar

“Fortran 90 Programming”,T. M. R. Ellis, I. R. Philips, T. M. Lahey

“Fortran 90 Language Guide”, Wilhelm Gehrke

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 4 / 43

Page 5: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

History

The early days...

Up tp 1954

Machine language (0,1 - binary)

Assembler (mnemonics)

→ Problem: Machine dependent + Higher-level language should beunderstandable by both humans and machines.

1954 - 1957

IBM team led by John Backus developed the first higher levellanguage: Fortran (Formula Translator)

→ very successful

1966 - First standard Fortran

Relatively machine independent

Was widely available

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 5 / 43

Page 6: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

History

Next standard: Fortran 77

Column 1-6

1: Line is a comment if a “c” or a“*” is inserted2-5: Labels for “GOTO” or“FORMAT” statements6: Any symbol beside blank or “0”→ line continues

Column 7-72

Actual Fortran statements

Column 73-80

Comments, not read by compiler,originally for sequence numbers ofpunched cards

Column 6

Any symbol beside blank or “0”→ line continues

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 6 / 43

Page 7: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

History

General Remarks:

Your program should be:

efficient (in both CPU time and memory)

readable (documentation, variable names, indentation,...)

portable (machine independent, compiler independent)

modular (subroutines can be used otherwise)

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 7 / 43

Page 8: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Fortran 90

Fortran 90 Program

A program consists of modules, like

Program

Subroutine

Function

Interface

Module

Fortran 90 Modules

Every module consists of

(Documentation)

Header

Declaration Part (variabledeclaration, use statements)

Execution Part

End

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 8 / 43

Page 9: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Declaration Part

Declaration Part

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 9 / 43

Page 10: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Declaration Part

Declaration Part - Variables and Constants

Variable names are symbolic references for positions within thememory.They are reserved already by the compiler, but get their valuesassigned at runtime.The memory for constants is already filled with the value atcompilation.Declare all variables and constants explicitly!(Implicit: I-N - Integer, A-H and O-Z - Real)

Fortran 77

IMPLICIT NONE INTEGER c REAL ix,x,y,z CHARACTER*10 name LOGICAL a DOUBLE PRECISION b

Fortran 90

IMPLICIT NONEINTEGER (kind=4) :: cREAL (kind=4) :: ix, x, y, zCHARACTER (len=10) :: nameLOGICAL :: aREAL (kind=8) :: b

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 10 / 43

Page 11: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Declaration Part

A quick side note on the binary system

Integer values:

16 bit (2 byte): [-32.768, 32.767] up to 214

32 bit (4 byte): [-2.147.483.648, 2.147.483.648] up to 230

27 26 25 24 23 22 21 20

1 1 0 1 0 0 0 1 = 209

0 0 0 0 0 0 1 1 = 3

Floating point values:

24 23 22 21 20 2−1 2−2 2−3

1 1 0 1 0 0 0 1 = 26.125

0 0 0 0 0 0 1 1 = 0.375

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 11 / 43

Page 12: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Declaration Part

Floating Point numbers

SINGLE PRECISION (32 bit or 4 byte)

DOUBLE PRECISION (64 bit or 8 byte)

Sign: Size = 1 bitExponent: Size = 8 bit (single), 11 bit (double)Significand: Size = 23 bit (single), 52 bit (double)

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 12 / 43

Page 13: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Declaration Part

Floating Point numbers

Roundoff error

Finite accuracy of number representationDecimal: π,

√2, 1

3 Binary: 0.1

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 13 / 43

Page 14: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Declaration Part

Machine Accuracy εm

The smallest number that can be added to 1. and gives as a result anumber that is different to 1.For a real number (4 byte) typically 3× 10−8

For example:1.E07 + 1. = 1.E07 → no matter how often you perform this calculation

Error estimation

For a randomly distributed error, after N operations: ≈√

Nεm

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 14 / 43

Page 15: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Declaration Part

KIND - A side mark to the topic of portability

It is up to each compiler configuration to decide what kind numbers areassociated with each type and kind variation → kind value on its ownshould not be used across platforms! To make sure the accuracy of youprogram is machine independent use the intrinsic functions:

INTEGER, PARAMETER :: intkind = SELECTED INT KIND (2)

INTEGER, PARAMETER :: realkind = SELECTED REAL KIND(P=15,R=307)

! P ... Precision (f.e. 15 significant digits), R ... Range (f.e. [10−307, 10307] )

INTEGER (KIND = intkind) :: i

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

Error / accuracy / range estimation:

KIND(x) Returns the kind type

HUGE(x) Returns the largest number

PRECISION(x) Returns the decimal precision

EPSILON(x) Smallest difference between two reals

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 15 / 43

Page 16: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Declaration Part

Other options in the declaration part

PARAMETERINTEGER, PARAMETER :: imax = 100000

! whats the difference to that:

INTEGER:: imax = 100000

REAL, PARAMETER :: pi = 4. * ATAN (1.)

Parameter cannot be changed withinthe program.Memory gets the value already atruntime.

DIMENSIONINTEGER :: i, j

REAL, DIMENSION (100) :: x, y, temp1D

REAL, DIMENSION(100,100) :: temp

DO i = 1,100,1

x(i) = REAL(i)

y(i) = REAL(i)

DO j = 1,100,1

temp(i,j) = 5. + 0.5 * &

SIN(x(i)) * COS(x(i)*y(j))

ENDDO

ENDDO

! Not in F77 :

temp1D = 0. temp1D = temp (50,:)

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 16 / 43

Page 17: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Declaration Part

Other options in the declaration part

ALLOCATABLEINTEGER :: i, j, nsteps

REAL, DIMENSION (:), ALLOCATABLE :: x, y

REAL, DIMENSION(:,:), ALLOCATABLE :: temp

write (*,*) ’how many steps in x and y direction?’

read (*,*) nsteps

allocate (x (nsteps) )

allocate (y (nsteps) )

allocate (temp (nsteps, nsteps) )

DO i = 1,100,1

x(i) = REAL(i)

y(i) = REAL(i)

DO j = 1,100,1

temp(i,j) = 5. + 0.5 * &

SIN(x(i)) * COS(x(i)*y(j))

ENDDO

ENDDO deallocate (x) deallocate (y) deallocate (temp)

OTHERS

INTENT(IN) (OUT) (INOUT)

PRIVATE

PUBLIC

SAVE

EXTERNAL

INTRINSIC

OPTIONAL

POINTER

TARGET

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 17 / 43

Page 18: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Execution Part

Execution Part

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 18 / 43

Page 19: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Execution Part

IF Statement

IF <logical expression> THEN

...

ENDIF

IF <logical expression> THEN

...

ELSE

...

ENDIF

IF <logical expression> THEN

...

IF <logical expression> THEN

...

ELSE IF <logical expression> THEN

...

ELSE

...

ENDIF

ENDIF

Logical Expressions

IF (a < b) THEN means: IF ( (a < b) == .true.) THEN

(a < b): relational ( < <= > >= == /= )

( .LT. .LE. .GT. .GE. .EQ. .NE. )

(a < b) .AND. (c > d):

logical (.NOT. .AND. .OR. .EQV. .NEQV.)

Relational expressions have a higher priority than

logical expressions.

Question!

!What could that mean:

IF (a) b=b+1

!Or that:

IF (r < ’N’) EXIT

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 19 / 43

Page 20: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Execution Part

CASE Construct

...INTEGER (kind=1) :: month...SELECT CASE (month)CASE (12,1,2)

write (*,*) ’Winter’CASE (3:5)

write (*,*) ’Spring’CASE (6:8)

write (*,*) ’Summer’CASE (9:11)

write (*,*) ’Autumn’CASE DEFAULT

write (*,*) ’Error: Something is wrong with your date’

END SELECT

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 20 / 43

Page 21: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Execution Part

DO Loop

INTEGER (kind = 1) :: x

INTEGER (kind = 2) :: f x

DO x = 1, 10, 2

f x = x*x + 10

write (*,*) x, f x

ENDDO

INTEGER (kind = 1) :: x

INTEGER (kind = 2) :: f x

x=1

DO

f x = x*x + 10.

write (*,*) x, f x

IF (x > 10) EXIT

x = x+2.

ENDDO

INTEGER (kind = 2) :: ix, iy

REAL (kind = 4) :: x, y, f xy

DO ix = -30, 30, 1

x = REAL(ix) / 10.

DO iy = -30, 30, 1

y = REAL(iy) / 10.

f xy = (x**2 + 2.5*y**2-yy)*exp(1.-(x**2+y**2))

write (*,*) x, y, f x

ENDDO

ENDDO

Be careful: What is the problem here?

INTEGER (kind = 2) :: ix, iy

REAL (kind = 4) :: x, y, f xy

ix= -30; iy= -30

DO

x = REAL(ix) / 10.

DO

y = REAL(iy) / 10.

f xy = (x**2 + 2.5*y**2-yy)*exp(1.-(x**2+y**2))

write (*,*) x, y, f x

IF (iy .gt. 30) EXIT

iy = iy + 1

ENDDO

IF (ix .gt. 30) EXIT

ix = ix + 1

ENDDO

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 21 / 43

Page 22: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Execution Part

DO Loop

INTEGER (kind = 1) :: x

INTEGER (kind = 2) :: f x

DO x = 1, 10, 2

f x = x*x + 10

write (*,*) x, f x

ENDDO

INTEGER (kind = 1) :: x

INTEGER (kind = 2) :: f x

x=1

DO

f x = x*x + 10.

write (*,*) x, f x

IF (x > 10) EXIT

x = x+2.

ENDDO

Loop Counter

Avoid infinite loops :INTEGER (kind = 4), PARAMETER :: imax = 100000

INTEGER (kind = 4) :: i

i = 0

DO

IF (i > imax) EXIT

i = i+1

ENDDO

INTEGER (kind = 2) :: ix, iy

REAL (kind = 4) :: x, y, f xy

DO ix = -30, 30, 1

x = REAL(ix) / 10.

DO iy = -30, 30, 1

y = REAL(iy) / 10.

f xy = (x**2 + 2.5*y**2-yy)*exp(1.-(x**2+y**2))

write (*,*) x, y, f x

ENDDO

ENDDO

Corrected version

INTEGER (kind = 2) :: ix, iy

REAL (kind = 4) :: x, y, f xy

ix= -30 ! ; iy= -30

DO

iy= -30

x = REAL(ix) / 10.

DO

y = REAL(iy) / 10.

f xy = (x**2 + 2.5*y**2-yy)*exp(1.-(x**2+y**2))

write (*,*) x, y, f x

IF (iy .gt. 30) EXIT

iy = iy + 1

ENDDO

IF (ix .gt. 30) EXIT

ix = ix + 1

ENDDO

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 22 / 43

Page 23: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Modules

F90 Modules

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 23 / 43

Page 24: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Modules

Subroutines

Example:

PROGRAM test

IMPLICIT NONE

INTEGER :: type

REAL :: r, p, d, g

...

call equation of state (type, t, p, d, g)

...

END PROGRAM test

SUBROUTINE equation of state (type, temp, pres, &

dens, gamma)

IMPLICIT NONE

INTEGER :: type

REAL :: temp, pres, dens, gamma

...

END SUBROUTINE equation of state

Advantages:

Keeps the code structured

Test each code segmentsseparately

Include already existingsegments→ Numerical Recipes !!!

Use a given segmentfrequently in a code

Use a self-written subroutine indifferent programs

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 24 / 43

Page 25: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Modules

Functions

A function itself needs a variable declaration and gives back a value.

Syntax

PROGRAM mainIMPLICIT NONEREAL :: plummer dens, edge dens, totalmass, &plummer rad, cutoff rad...edge dens = plummer dens(totalmass, plummer rad, cutoff rad)

END PROGRAM main

FUNCTION plummer dens (totalmass, plummer rad, cutoff rad)IMPLICIT NONEREAL :: plummer dens, edge dens, totalmass, plummer rad,cutoff rad

plummer dens = ...END FUNCTION plummer dens

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 25 / 43

Page 26: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Modules

Modules

Sharing variables between different routines:

Syntax

MODULE constantsIMPLICIT NONEREAL, PARAMETER :: pi = 4.*ATAN(1.)REAL, PARAMETER :: Msol = 1.98892E33REAL, PARAMETER :: parsec = 3.08568025E18

END MODULE constants

PROGRAM mainUSE constants, ONLY: pi

WRITE (*,*) ’Pi = ’, piEND

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 26 / 43

Page 27: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Modules

Main program of the powerful FLASH3.2 code

program Flash

use Driver interface

implicit none

call Driver initFlash()

call Driver evolveFlash()

call Driver finalizeFlash()

end program Flash

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 27 / 43

Page 28: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Back to F77

Back to Fortran 77

Common Block - Syntax

PROGRAM mainIMPLICIT NONEREAL a, bCOMMON /coeff/ a, b

CALL solveEND PROGRAM main

SUBROUTINE solveIMPLICIT NONEREAL a, bCOMMON /coeff/ a, b...END SUBROUTINE solve

Common Block + Include

PROGRAM mainINCLUDE ’main.inc’CALL solve

END PROGRAM main

SUBROUTINE solveINCLUDE ’main.inc’...END SUBROUTINE solve

! file ’main.inc’ :IMPLICIT NONEREAL a,bCOMMON /coeff/ a, b

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 28 / 43

Page 29: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Back to F77

Compiler and Linker

We use: gfortran <options> <infile 1> <infile 2> ...To find out about the options:> man gfortran

Some helpful options:-fdefault-integer-8 : Set the default integer and logical types to the8 byte wide type-fdefault-real-8 : Set the default real type to the 8 byte wide type-fimplicit-none : Equivalent of adding “implicit none” to the start ofevery procedure-o <output>: Output file not default (a.out) but <output>

The compiler is treating every routine separately → no error message whenthe declarations of values which are exchanged do not fit together!

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 29 / 43

Page 30: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Gnuplot

Homepage: www.gnuplot.info

Freely distributed

Command line driven

Available for a lot of different platforms

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 30 / 43

Page 31: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Figure: defaultSylvia Plockinger () An Introduction to Fortran March 10, 2011 31 / 43

Page 32: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Figure: defaultSylvia Plockinger () An Introduction to Fortran March 10, 2011 32 / 43

Page 33: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Figure: defaultSylvia Plockinger () An Introduction to Fortran March 10, 2011 33 / 43

Page 34: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Figure: defaultSylvia Plockinger () An Introduction to Fortran March 10, 2011 34 / 43

Page 35: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Figure: defaultSylvia Plockinger () An Introduction to Fortran March 10, 2011 35 / 43

Page 36: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Figure: defaultSylvia Plockinger () An Introduction to Fortran March 10, 2011 36 / 43

Page 37: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Try out the following with the 3D data from last week:set pm3d at bset contour baseset surfaceset view 70,60,1.0,1.5set dgrid3d 50, 50set hidden3dshow contour

splot "data3D.dat" u 1:2:3 w line palette

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 37 / 43

Page 38: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 38 / 43

Page 39: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 39 / 43

Page 40: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 40 / 43

Page 41: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 41 / 43

Page 42: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 42 / 43

Page 43: An Introduction to Fortran - univie.ac.athomepage.univie.ac.at/nigel.mitchell/NumPrac/Yr2011/Fortran.pdf · \Fortran 90/95 for Scientists and Engineers", Stephen J. Chapman ... Sylvia

Gnuplot

Sylvia Plockinger () An Introduction to Fortran March 10, 2011 43 / 43