44
Real Programs Introductory Fortran Programming Part 5 Gunnar Wollan 1 Dept. of Geosciences, University of Oslo 1 January 2007 Wollan Introductory Fortran Programming Part 5

Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

  • Upload
    doannga

  • View
    224

  • Download
    2

Embed Size (px)

Citation preview

Page 1: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

Introductory Fortran Programming Part 5

Gunnar Wollan1

Dept. of Geosciences, University of Oslo1

January 2007

Wollan Introductory Fortran Programming Part 5

Page 2: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

Outline

1 From small examples to real programs

Wollan Introductory Fortran Programming Part 5

Page 3: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

List of Topics

1 From small examples to real programs

Wollan Introductory Fortran Programming Part 5

Page 4: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

Solving a real problem

Let us take a look at a problem from oceanography

Studies of bordered layers can often be done in approximately

one dimensional models

A well known example of this is the Ekman Layer

The mathematics solving this problem is found Click here

Wollan Introductory Fortran Programming Part 5

Page 5: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

Solving a real problem

Let us take a look at a problem from oceanography

Studies of bordered layers can often be done in approximately

one dimensional models

A well known example of this is the Ekman Layer

The mathematics solving this problem is found Click here

Wollan Introductory Fortran Programming Part 5

Page 6: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

Solving a real problem

Let us take a look at a problem from oceanography

Studies of bordered layers can often be done in approximately

one dimensional models

A well known example of this is the Ekman Layer

The mathematics solving this problem is found Click here

Wollan Introductory Fortran Programming Part 5

Page 7: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

Solving a real problem

Let us take a look at a problem from oceanography

Studies of bordered layers can often be done in approximately

one dimensional models

A well known example of this is the Ekman Layer

The mathematics solving this problem is found Click here

Wollan Introductory Fortran Programming Part 5

Page 8: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

The solution of this problem is using complex numbers and we

will see the use of intrinsic functions to handle the real and

imaginary part of a complex number

So let us start with some code

PROGRAM ekmanspiralIMPLICIT NONE!// Declaration of constant valuesREAL, PARAMETER :: uis = 1.5 ! Speed in X-directionREAL, PARAMETER :: vis = 2.5 ! Speed in Y-directionINTEGER, PARAMETER :: l = -30 ! Start valueINTEGER, PARAMETER :: n = 101 ! Array lengthREAL, PARAMETER :: K = 1.0E-3 ! Eddy-viscosityREAL, PARAMETER :: f = 1.4E-4 ! Calculation constantINTEGER,PARAMETER :: lun = 11 ! Logical unit number

Wollan Introductory Fortran Programming Part 5

Page 9: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

The solution of this problem is using complex numbers and we

will see the use of intrinsic functions to handle the real and

imaginary part of a complex number

So let us start with some code

PROGRAM ekmanspiralIMPLICIT NONE!// Declaration of constant valuesREAL, PARAMETER :: uis = 1.5 ! Speed in X-directionREAL, PARAMETER :: vis = 2.5 ! Speed in Y-directionINTEGER, PARAMETER :: l = -30 ! Start valueINTEGER, PARAMETER :: n = 101 ! Array lengthREAL, PARAMETER :: K = 1.0E-3 ! Eddy-viscosityREAL, PARAMETER :: f = 1.4E-4 ! Calculation constantINTEGER,PARAMETER :: lun = 11 ! Logical unit number

Wollan Introductory Fortran Programming Part 5

Page 10: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

These constant declarations are the initial conditions for the

aplication

Changing one or more of these values will give different results

of the simulation

Wollan Introductory Fortran Programming Part 5

Page 11: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

These constant declarations are the initial conditions for the

aplication

Changing one or more of these values will give different results

of the simulation

Wollan Introductory Fortran Programming Part 5

Page 12: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

These constant declarations are the initial conditions for the

aplication

Changing one or more of these values will give different results

of the simulation

Wollan Introductory Fortran Programming Part 5

Page 13: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

A set of complex arrays for solving the equations referred to in

the code

PROGRAM ekmanspiral....

!// Declaration of complex arraysCOMPLEX, DIMENSION(n) :: z = 0.0 ! Depth (0 to -H)COMPLEX, DIMENSION(n) :: a = 0.0 ! Equation 7COMPLEX, DIMENSION(n) :: b = 0.0 ! Equation 8COMPLEX, DIMENSION(n) :: c = 0.0 ! Equation 9COMPLEX, DIMENSION(n) :: cm = 0.0 ! Equation 10, 11COMPLEX, DIMENSION(n) :: d = 0.0 ! Equation 6COMPLEX, DIMENSION(n) :: dm = 0.0 ! Equation 12COMPLEX, DIMENSION(n) :: W = 0.0 ! Complex speed

Wollan Introductory Fortran Programming Part 5

Page 14: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

These arrays containing complex values are intermediate

arrays taken from the respective equations in the matematical

solution

The array W will contain the result of the simulation

Note the initialization of the arrays in the declarations

Remember that the initialization values only are used in the

first call to the method. To be certain to give the arrays a

initial value always do the initialization explicit in the method

after the declarations

Wollan Introductory Fortran Programming Part 5

Page 15: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

These arrays containing complex values are intermediate

arrays taken from the respective equations in the matematical

solution

The array W will contain the result of the simulation

Note the initialization of the arrays in the declarations

Remember that the initialization values only are used in the

first call to the method. To be certain to give the arrays a

initial value always do the initialization explicit in the method

after the declarations

Wollan Introductory Fortran Programming Part 5

Page 16: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

These arrays containing complex values are intermediate

arrays taken from the respective equations in the matematical

solution

The array W will contain the result of the simulation

Note the initialization of the arrays in the declarations

Remember that the initialization values only are used in the

first call to the method. To be certain to give the arrays a

initial value always do the initialization explicit in the method

after the declarations

Wollan Introductory Fortran Programming Part 5

Page 17: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

These arrays containing complex values are intermediate

arrays taken from the respective equations in the matematical

solution

The array W will contain the result of the simulation

Note the initialization of the arrays in the declarations

Remember that the initialization values only are used in the

first call to the method. To be certain to give the arrays a

initial value always do the initialization explicit in the method

after the declarations

Wollan Introductory Fortran Programming Part 5

Page 18: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

These arrays containing complex values are intermediate

arrays taken from the respective equations in the matematical

solution

The array W will contain the result of the simulation

Note the initialization of the arrays in the declarations

Remember that the initialization values only are used in the

first call to the method. To be certain to give the arrays a

initial value always do the initialization explicit in the method

after the declarations

Wollan Introductory Fortran Programming Part 5

Page 19: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

More declarations

!// Declaration of REAL arraysREAL, DIMENSION(n) :: u ! Contains the real part

! of WREAL, DIMENSION(n) :: v ! Contains the imaginary

! part of W!// Declaration of complex variablesCOMPLEX :: dz ! Grid distance between

! two pointsCOMPLEX :: delta ! Delta = dz^2*f/KCOMPLEX :: wis ! Complex speed at border

! condition icefloe level!// Declaration of real variablesREAL :: ximg ! Help variable!// Declaration of integer variablesINTEGER :: i ! Index variableINTEGER :: rstat ! Return status variable

Wollan Introductory Fortran Programming Part 5

Page 20: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The array u will be written to a file and can be used as input

to a plotting program

Wollan Introductory Fortran Programming Part 5

Page 21: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The array u will be written to a file and can be used as input

to a plotting program

Wollan Introductory Fortran Programming Part 5

Page 22: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Declarations and initialization

!// Declaration of character stringCHARACTER(LEN=80) :: fname ! Output filename!// Set the filenamefname = "result.dat"!// Initialize ximg to the imaginary part of 0.0ximg = IMAG(CMPLX(0.0)) ! IMAG and CMPLX are

! intrinsic functions!// Initializing z array by calling the!// subroutine linspaceCALL linspace(z, l, 0, n)

Wollan Introductory Fortran Programming Part 5

Page 23: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The ximg is inititalized with the imaginary part of a complex

zero

The intrinsic function IMAG() returns the imaginary part of

the complex argument

The other intrinsic function CMPLX() returns the complex

number of the argument

Wollan Introductory Fortran Programming Part 5

Page 24: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The ximg is inititalized with the imaginary part of a complex

zero

The intrinsic function IMAG() returns the imaginary part of

the complex argument

The other intrinsic function CMPLX() returns the complex

number of the argument

Wollan Introductory Fortran Programming Part 5

Page 25: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The ximg is inititalized with the imaginary part of a complex

zero

The intrinsic function IMAG() returns the imaginary part of

the complex argument

The other intrinsic function CMPLX() returns the complex

number of the argument

Wollan Introductory Fortran Programming Part 5

Page 26: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The ximg is inititalized with the imaginary part of a complex

zero

The intrinsic function IMAG() returns the imaginary part of

the complex argument

The other intrinsic function CMPLX() returns the complex

number of the argument

Wollan Introductory Fortran Programming Part 5

Page 27: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Initialization

!// Setting up other valuesdz = z(2) - z(1) ! Distance between two of

! the depth levelsdelta = dz**2 * f / kwis = uis + ximg * visa = 0.; b = 0.; c = 0.d = 0.; cm = 0.; dm = 0.DO i = 2, n - 1a(i) = -1.0 ! Equation 7b(i) = 2.0 + ximg * delta ! Equation 9c(i) = -1.0 ! Equation 8

END DO

Wollan Introductory Fortran Programming Part 5

Page 28: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

Here we initialize the rest of the variables

Note that the DO-loop initializes the three arrays containing

the values from the tri-diagonal matrix

Wollan Introductory Fortran Programming Part 5

Page 29: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

Here we initialize the rest of the variables

Note that the DO-loop initializes the three arrays containing

the values from the tri-diagonal matrix

Wollan Introductory Fortran Programming Part 5

Page 30: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

Here we initialize the rest of the variables

Note that the DO-loop initializes the three arrays containing

the values from the tri-diagonal matrix

Wollan Introductory Fortran Programming Part 5

Page 31: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Calculations

b(1) = 1 ! Equation 8b(n) = 1 ! Equation 8d(n) = wis ! Equation 6cm(1) = c(1) / b(1) ! Equation 10dm(1) = d(1) / b(1) ! Equation 10DO i = 2, n

cm(i) = c(i) / (b(i) - a(i) * cm(i-1)) ! Equation 11dm(i) = (d(i) - a(i) * dm(i-1)) / &(b(i) - a(i) * cm(i-1)) ! Equation 12

END DO

Wollan Introductory Fortran Programming Part 5

Page 32: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

Here we perform calculations from some of the equations

Note that the index in the do-loop starts at the value 2

This is done not to overwrite the values already set in element

1 in the respective arrays

Wollan Introductory Fortran Programming Part 5

Page 33: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

Here we perform calculations from some of the equations

Note that the index in the do-loop starts at the value 2

This is done not to overwrite the values already set in element

1 in the respective arrays

Wollan Introductory Fortran Programming Part 5

Page 34: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

Here we perform calculations from some of the equations

Note that the index in the do-loop starts at the value 2

This is done not to overwrite the values already set in element

1 in the respective arrays

Wollan Introductory Fortran Programming Part 5

Page 35: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

Here we perform calculations from some of the equations

Note that the index in the do-loop starts at the value 2

This is done not to overwrite the values already set in element

1 in the respective arrays

Wollan Introductory Fortran Programming Part 5

Page 36: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Calculations

W(n) = dm(n) ! Equation 13DO i = n - 1, 1, -1

W(i) = dm(i) - W(i+1) * cm(i) ! Equation 14END DODO i = 1, n

u(i) = REAL(W(i)) ! Real part of w(i), equation 15v(i) = IMAG(W(i)) ! Imaginary part of w(i),

! equation 16END DO!// Open the output fileOPEN(UNIT=lun,FILE=fname,FORM=’FORMATTED’,IOSTAT=rstat)DO i = 1,n

WRITE(UNIT=lun,FMT=’(F12.8,A1,F12.8)’,IOSTAT=rstat)&u(i), ’ ’,REAL(z(i))

END DOCLOSE(lun)

Wollan Introductory Fortran Programming Part 5

Page 37: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Linspace, declarations

SUBROUTINE linspace(z, l, k, n)IMPLICIT NONE!// Argument declarationsCOMPLEX, DIMENSION(n) :: zINTEGER :: lINTEGER :: kINTEGER :: n!// Local variablesINTEGER :: iREAL :: d, x, y

Wollan Introductory Fortran Programming Part 5

Page 38: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The linspace subroutine is ”borrowed” from a similiar function

in Matlab

The complex array z is filled with n equal spaced numbers

between the two endpoints l and k

Wollan Introductory Fortran Programming Part 5

Page 39: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The linspace subroutine is ”borrowed” from a similiar function

in Matlab

The complex array z is filled with n equal spaced numbers

between the two endpoints l and k

Wollan Introductory Fortran Programming Part 5

Page 40: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The linspace subroutine is ”borrowed” from a similiar function

in Matlab

The complex array z is filled with n equal spaced numbers

between the two endpoints l and k

Wollan Introductory Fortran Programming Part 5

Page 41: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Linspace, calculations

x = FLOAT(k)y = FLOAT(l)d = (x - y) / nPRINT *, d, k, l, nz(1) = FLOAT(l)DO i = 2, n-1z(i) = z(i-1) + d

END DOz(1) = yz(n) = xRETURN

END SUBROUTINE linspace

Wollan Introductory Fortran Programming Part 5

Page 42: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The step variable d is calculated from the difference of the

endpoints divided by the number of element in the array

Note that since the endpoint arguments are integer numbers

we have to explixitly convert them to floating point numbers

Wollan Introductory Fortran Programming Part 5

Page 43: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The step variable d is calculated from the difference of the

endpoints divided by the number of element in the array

Note that since the endpoint arguments are integer numbers

we have to explixitly convert them to floating point numbers

Wollan Introductory Fortran Programming Part 5

Page 44: Introductory Fortran Programming Part 5 - …folk.uio.no/gunnarw/CSE-FL/Fortran/PART5/cse-fl.pdfReal Programs Introductory Fortran Programming Part 5 Gunnar Wollan1 Dept. of Geosciences,

Real Programs

The Ekman Layer

Some short comments on the code

The step variable d is calculated from the difference of the

endpoints divided by the number of element in the array

Note that since the endpoint arguments are integer numbers

we have to explixitly convert them to floating point numbers

Wollan Introductory Fortran Programming Part 5