3. repetitive structures (loops)

29
FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI 16 3. Repetitive Structures (Loops) We can make a program to repeat sections of statements (iterate) by using the DO loop construct. There are three forms: The DO loop with a counter, The DO-EXIT Construct The DO-WHILE Construct. 3.1 The DO Loop with a Counter In this type of looping, the repetition is controlled by a counter. It has the following general form: DO counter = initial value , limit , step size . Block of statements . END DO For example DO I = 4, 10, 2 PRINT *, I, I**2, I**3 END DO gives: 4 16 64 6 36 216 8 64 512 10 100 1000 For example DO I = 10, 4, -2 PRINT *, I, I**2, I**3 END DO gives: 10 100 1000 8 64 512 6 36 216 4 16 64

Upload: others

Post on 18-Dec-2021

9 views

Category:

Documents


0 download

TRANSCRIPT

Page 1: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

16

3. Repetitive Structures (Loops) We can make a program to repeat sections of statements (iterate) by

using the DO loop construct. There are three forms:

The DO loop with a counter,

The DO-EXIT Construct

The DO-WHILE Construct.

3.1 The DO Loop with a Counter In this type of looping, the repetition is controlled by a counter. It has the following general form: DO counter = initial value , limit , step size

. Block of statements .

END DO

For example DO I = 4, 10, 2

PRINT *, I, I**2, I**3 END DO

gives: 4 16 64 6 36 216 8 64 512 10 100 1000

For example DO I = 10, 4, -2

PRINT *, I, I**2, I**3 END DO

gives: 10 100 1000 8 64 512 6 36 216 4 16 64

Page 2: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

17

Ex: Write a program to find the sum of the numbers from 1-100

PROGRAM SUMMATION

IMPLICIT NONE INTEGER :: i, sum sum=0 Do i=1,100 sum=sum + i END DO PRINT *, "sum=" ,sum

END PROGRAM SUMMATION

3.2 DO-EXIT Construct In this type of looping, the repetition is controlled by a logical expression (condition). It has the following general form:

DO statement sequence_1 IF ( a simple or compound condition ) EXIT statement sequence_2

END DO

The loop is repeated until the condition (a logical expression) in IF

statement becomes false. If the condition is true, the loop is terminated by EXIT

statement. This loop is used when we do not know how many iterations are required. The following program section outputs the even numbers 10, 8, ... , 2 and their squares:

N=10 ! initial value DO PRINT *,N,N**2 IF(N<4) EXIT N=N-2 ! decrement END DO Output:

10 100 8 64 6 36 4 16 2 4

Page 3: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

18

Study the following piece of code DO PRINT *, "Enter the radius of the circle:" READ *, r PRINT *, "Area is ", 3.14*r**2 PRINT *, "Do you want to calculate another area? (Y/N):" READ *, response IF (response == "N") EXIT END DO After Execution : Enter the radius of the circle: 10 Area is 314.000000 Do you want to calculate another area? (Y/N): N

3.3 CYCLE Statement in DO Loop

The general form is :

DO statement sequence_1 IF ( a simple or compound condition ) CYCLE

statement sequence_2 IF ( a simple or compound condition ) EXIT statement sequence_3

END DO When the CYCLE statement is executed control goes back to the top of the

loop. When the EXIT statement is executed control goes to the end of the loop

and the loop is terminated.

Example of the use of DO-CYCLE construct: DO READ *,x IF (x == 0) CYCLE IF(x<0) EXIT F = 1.0/x PRINT *, x, F END DO

i = 0 DO i = i + 1 IF (i>=50 .AND. i<= 59) CYCLE IF (i > 100) EXIT PRINT *, i END DO

Page 4: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

19

Ex: Write a program to find the mean (excluding zeros) of a list of real values.

PROGRAM Mean

!----------------------------------------------- !The mean of all non-zero entries is calculated. !----------------------------------------------- IMPLICIT NONE INTEGER :: Count REAL :: V, Sum Sum = 0 Count = 0 PRINT *, "Input the values." DO READ *, V IF ( V==0 ) CYCLE IF ( V < 0 ) EXIT Sum = Sum + V Count = Count + 1 END DO PRINT *, "The sum is ", Sum PRINT *, "The mean is ", Sum / REAL(Count) END PROGRAM Mean

Ex: Write a program to find the factorial of an integer.

PROGRAM Factorial !------------------------------------------------ ! Program to compute the factorial of an integer. !------------------------------------------------ IMPLICIT NONE INTEGER :: N, F PRINT *, "Input an integer N" READ *, N F = 1 DO IF (N==0) EXIT F = F*N N=N-1 END DO PRINT *," Factorial = ", F END PROGRAM Factorial

Page 5: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

21

3.4 DO-WHILE Construct

It has the following general form:

DO WHILE( a simple or compound condition ) ... statement sequence ...

END DO Here statement sequence is executed repeatedly as long as the condition is true. Example of the use of a DO-WHILE construct:

N=10 DO WHILE(N>=2) PRINT *,N,N**2 N=N-2 END DO Gives:

10 100 8 64 6 36 4 16

2 4

Ex: Write a program to find the average of 20 numbers (use DO WHILE).

PROGRAM SUM_OF_20REALS

IMPLICIT NONE INTEGER :: I=1 REAL :: x, sum=0.0,AV DO WHILE(I<=20) READ *,x sum = sum + x I=I+1 END DO AV=sum/REAL(20) PRINT *,"Average=",AV END PROGRAM SUM_OF_20REALS

Page 6: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

21

3.5 Named and Nested DO Loops Nested loops (one loop is inside the other) may be given names (labels) and they have the following form:

outer: DO i = 1,10 inner: DO j = 1,10

statements .

END DO inner END DO outer

Ex : Write a program finds the value of Z form the following formula:

∑ ∑

PROGRAM NESTED

IMPLICIT NONE INTEGER :: i, j, Z=0 outer: DO i=0,5 inner: DO j=0,4 Z=Z+(i*j)

END DO inner END DO outer PRINT *, "Z=",Z END PROGRAM NESTED

Ex: Write a program to find the sum of the following series :

PROGRAM ExpX IMPLICIT NONE INTEGER :: i,j,n,fact REAL :: x, sum PRINT *, "Input a number." READ *, x, n sum = 1 outer: DO i = 1 , n fact=1

Inner loop

outer loop

Page 7: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

22

inner: DO j=1,i fact=fact*j END DO inner sum=sum +(x**i)/REAL(fact) END DO outer PRINT *, "sum= ", sum END PROGRAM ExpX

Ex: Write a program to find the sum of the following series.

PROGRAM SERIES_SUM IMPLICIT NONE INTEGER :: i, j=2, r=1, n, f REAL :: x, sum=0 READ *, x, n Outer: DO WHILE (j<=n) i=1 f=1 inner: DO WHILE (i<=j) f=f*i i=i+1 END DO inner sum=sum +(f/x**j)*r j=j+2; r= -1*r END DO outer PRINT *,"sum=", sum END PROGRAM SERIES_SUM

H.W. Write a program to find the sum of the odd numbers from 1-100

H.W. Write a program to find the sum of the following series (10 terms).

Page 8: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

23

4. Formatted Output in FORTRAN 90 This section gives you the basics rules of formatting output in

your FORTRAN programs. The PRINT statement is used to send output to the standard output unit ( usually your monitor, or sometimes your printer ) of your computer system. The general forms of PRINT statement are :

PRINT *, output-list (free-format PRINT statement) PRINT '(format)' , output-list (formatted PRINT statement) In the formatted form, the " * " is replaced by a certain format. For examples : PRINT '(F5.3)', 1.2345

PRINT '(I4)', 10000 4.1 INTEGER Output: The I Descriptor The general form of these descriptors are as follows:

rIw and rIw.m I : is for INTEGER w : is the width of field, which indicates that an integer should be printed

with w positions.

m : indicates that at least m positions (of the w positions) must contain digits. If the number to be printed has fewer than m digits, 0's are filled.

r : is the repetition indicator, which gives the number of times the edit descriptor should be repeated. For example, 3I5.3 is equivalent to I5.3, I5.3, I5.3.

The sign of a number also needs one position. Thus, if -234 is printed, w must be larger than or equal to 4. The sign of a positive number is not printed. Examples Look at the following example.

INTEGER :: a=123, b=-123, c=123456 PRINT '(I5)' , a 1 2 3 PRINT '(I5.2)' , a 1 2 3 PRINT '(I5.4)' , a 0 1 2 3 PRINT '(I5.5)' , a 0 0 1 2 3 PRINT '(I5)' , b - 1 2 3 PRINT '(I5.2)' , b - 1 2 3 PRINT '(I5.4)' , b - 0 1 2 3 PRINT '(I5.5)' , b * * * * * PRINT '(I5.2)' , c * * * * *

Consider the following example :

Page 9: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

24

INTEGER :: a = 3, b = -5, c = 128 PRINT '(3I4.2)' , a, b, c

The edit descriptor is 3I4.2 and the format is equivalent to (I4.2,I4.2,I4.2) because the repetition indicator is 3. The result is shown below:

0 3 - 0 5 1 2 8

4.2 REAL Output: The F Descriptor The Fw.d descriptor is for REAL output. The general form is:

rFw.d F is for REAL w is the width of field, which indicates that a real number should be

printed with w positions. d indicates the number of digits after the decimal point. r is the repetition indicator, which gives the number of times the edit

descriptor should be repeated. For example, 3F5.3 is equivalent to F5.3, F5.3, F5.3.

Examples Look at the following example.

REAL :: a=123.345, b=-123.345 PRINT '(F10.0)' , a 1 2 3 . PRINT '(F10.1)' , a 1 2 3 . 3 PRINT '(F10.2)' , a 1 2 3 . 3 4 PRINT '(F10.3)' , a 1 2 3 . 3 4 5 PRINT '(F10.4)' , a 1 2 3 . 3 4 5 0 PRINT '(F10.5)' , a 1 2 3 . 3 4 5 0 0 PRINT '(F10.6)' , a 1 2 3 . 3 4 5 0 0 0 PRINT '(F10.7)' , a * * * * * * * * * * PRINT '(F10.4)' , b - 1 2 3 . 3 4 5 0 PRINT '(F10.5)' , b - 1 2 3 . 3 4 5 0 0 PRINT '(F10.6)' , b * * * * * * * * * *

Consider the following example.

REAL :: a = 12.34, b = -0.945, c = 100.0 PRINT '(3F6.2)', a, b, c 1 2 . 3 4 - 0 . 9 5 1 0 0 . 0 0

Page 10: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

25

4.3 REAL Output: The E Descriptor The rEw.d descriptor is for REAL output. The printed numbers will be in an exponential form. The general form is:

rEw.d E is for REAL numbers in exponential forms.

w is the width of field, which indicates that a real number should be printed with w positions.

To print a number in an exponential form, it is first converted to a normalized form sxxx...xxx×10sxx, where s is the sign of the number and the exponent and x is a digit. For example, 12.345, -12.345, 0.00123 and -0.00123 are converted to 0.12345×102, -0.12345×102, 0.123×10-2 and -0.123×10-2. The Ew.d descriptor generates real numbers in the following form:

r is the repetition indicator, which gives the number of times the edit descriptor should be repeated. For example, 3E20.7E2 is equivalent to E20.7E2, E20.7E2, E20.7E2.

Examples In the following table, the PRINT statements use different E edit descriptors to print the value of 3.1415926. The PRINT statements are shown in the left and their corresponding output, all using 12 positions, are shown in the right. REAL :: PI=3.1415926 PRINT '(E12.5)',PI 0 . 3 1 4 1 6 E + 0 1 PRINT '(E12.4)',PI 0 . 3 1 4 2 E + 0 1 PRINT '(E12.3)',PI 0 . 3 1 4 E + 0 1

4.4 LOGICAL Output: The L Descriptor The rLw descriptor is for LOGICAL output. Fortran uses T and F to

indicate logical values true and false, respectively. The general form of this descriptor is :

rLw L is for LOGICAL w is the width of field, which indicates that a logical value should be

printed with w positions.

The output of a LOGICAL value is either T for .TRUE. or F for .FALSE. The single character value is shown in the right-most position

Page 11: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

26

and the remaining w-1 positions are filled with spaces. The is shown in the figure below.

r is the repetition indicator . Examples Let us look at the following example. There are two LOGICAL variables a and b with values .TRUE. and .FALSE., respectively. In the following table, the WRITE statements are shown in the left and their corresponding output are shown in the right.

LOGICAL :: a=.TRUE., b=.FALSE. PRINT '(L1,L2)' , a, b T F PRINT '(L3,L4)' , a, b T F

4.5 CHARACTER Output: The A Descriptor The rA and rAw descriptors are for CHARACTER output. The general form of these descriptors are as follows:

rA and rAw

A is for CHARACTER

w is the width of field, which indicates that a character string should be printed with w positions.

The output of the character string depends on two factors, namely the length of the character string and the value of w. Here are the rules:

If w is larger than the length of the character string, all characters of the string can be printed and spaces will be added. PRINT '(A6)',"12345" The five characters are printed and right-justified. The result is shown below:

1 2 3 4 5

If w is less than the length of the character string, then the string is truncated and only the left-most positions are printed.

PRINT '(A6)', "12345678" Only the first six characters are printed. The result is shown below:

1 2 3 4 5 6

Page 12: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

27

Let us look at the following example.

CHARACTER(LEN=5) :: a = "12345" CHARACTER :: b = "*" PRINT '(A1, A)', a, b 1 * PRINT '(A2, A)', a, b 1 2 * PRINT '(A3, A)', a, b 1 2 3 * PRINT '(A4, A)', a, b 1 2 3 4 * PRINT '(A5, A)', a, b 1 2 3 4 5 * PRINT '(A6, A)', a, b 1 2 3 4 5 * PRINT '(A7, A)', a, b 1 2 3 4 5 * PRINT '(A, A)', a, b 1 2 3 4 5 *

Page 13: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

28

5. Procedures (Sub-programs)

Procedures are used to fragment large programs into smaller units, each unit can perform a certain task. Procedures help us to understand the large programs. Procedures are of two types:

1. User-defined Functions 2. Subroutines

5.1 User-defined Functions

In addition to intrinsic functions, Fortran allows you to design your own functions. A function accepts some inputs from the main program. Every function has a name and independent values of inputs. The inputs are called parameters or arguments. A function may have one or more inputs but returns only one output to the main program.

Inputs Output (return value)

type FUNCTION function-name (arg1, arg2, ..., argn) IMPLICIT NONE ... name = an expression ...

END FUNCTION name

where : type is the type of the function (or type of the return value) . name is the Function name arg1, arg2, ..., argn (arguments) are inputs to the function.

For example a function that returns the sum of two integers can be defined as follows:

INTEGER FUNCTION Add(A,B) INTEGER :: A,B Add = A+B END FUNCTION Add

The function is called (تستدعى( by its name either through a variable or an expression .

Function

Page 14: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

29

Fortran 90 provides two basic types of functions :

Internal Functions are placed between a CONTAINS statement and

the END PROGRAM statement.

External Functions are placed after the main program (i.e. after the END

PROGRAM statement). PROGRAM Summation

IMPLICIT NONE INTEGER :: I,J,sum READ *,I,J sum = Add(I,J) PRINT *,"The sum is ",sum CONTAINS INTEGER FUNCTION Add(A,B)

INTEGER, INTENT(IN) :: A,B Add = A+B END FUNCTION Add END PROGRAM Summation

PROGRAM Summation

IMPLICIT NONE INTEGER :: I,J, sum, Add READ *,I,J sum = Add(I,J) PRINT *,"The sum is ", sum END PROGRAM Summation

INTEGER FUNCTION Add(A,B)

INTEGER, INTENT(IN) :: A,B Add = A+B END FUNCTION Add

The meaning of INTENT(IN) indicates that the function will only take the

value from the formal argument and must not change its content.

In this example we will consider the conversion of angles in degrees to radians. The formula for conversion is defined by:

PROGRAM Degrees2Radians IMPLICIT NONE REAL :: Degrees ! input REAL :: Radians ! output PRINT *, "Input the angle in degrees" READ *, Degrees Radians = Rad(Degrees) PRINT *,Degrees, "degrees= ", Radians, "Radians." CONTAINS REAL FUNCTION Rad(A) REAL, INTENT(IN):: A REAL, PARAMETER :: Pi = 3.141593 Rad = A * Pi/180. END FUNCTION Rad END PROGRAM Degrees2Radians

Page 15: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

31

Ex: Write a function finds the sum of two numbers, the main program calls the function to find the sum of four numbers.

PROGRAM Summation

IMPLICIT NONE REAL :: a, b, c, d, s1, s2, s READ *, a, b, c, d s1=sum(a, b) s2=sum(c, d) s=sum(s1,s2) PRINT *, "summation= ", s CONTAINS REAL FUNCTION sum(x, y) REAL, INTENT(IN) :: x, y sum=x + y END FUNCTION sum END PROGRAM summation

Ex: Write a function that finds the factorial of an integer, the main program calls the function to compute the combinations from the following formula.

PROGRAM Combinations IMPLICIT NONE INTEGER :: n, m ,f1 , f2, f3,fact REAL :: C PRINT *, "Enter the values of n and m :" READ *, n, m f1=fact(n) f2=fact(n-m) f3=fact(m) C=f1/(f2*f3) PRINT *, "Combinations = ", C END PROGRAM Combinations INTEGER FUNCTION fact(k) INTEGER, INTENT(IN) :: k INTEGER:: i, f=1 DO i=2, k f=f*i END DO fact=f END FUNCTION fact

Page 16: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

31

5.2 Subroutines Subroutines are similar to functions. Subroutines can be defined internally (following a CONTAINS statement) or externally (after the END PROGRAM statement). The major differences between functions and subroutines are as follows:

Functions take input and return a single number, character string, logical result, or array to the program that referenced it. Subroutines can return a large amount of output or no data (i.e. they can just perform a task such as printing results or displaying output) to the referencing program.

The name of a function is set to the returning value. A subroutine name does not contain a value. Output from a subroutine is returned via the arguments contained in the output list. (i.e. if you want to return three values you must have one argument in the argument list for each output value).

Functions are referenced in the main program structure by using their names in an expression. Subroutines are referenced using a CALL statement.

Inputs Outputs (return values)

The basic format of a subroutine description is as follows: SUBROUTINE name (argument-list) IMPLICIT NONE [specification part] [execution part] END SUBROUTINE The argument-list is a list of identifiers (variables) for the input and output to the subroutine. Subroutines are referenced (called) in main programs using a CALL statement.

CALL name (actual argument-list)

The actual argument-list contains the variables, constants, or expressions that are to be used by the subroutine.

Subroutine

Page 17: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

32

For example, a subroutine that returns area and circumference of a rectangle with sides x and y can defined as follows:

Internal Subroutine External Subroutine PROGRAM Rectangle IMPLICIT NONE REAL :: X,Y,A,C PRINT *,"Input the sides:" READ *,X,Y CALL Rect(X,Y, A,C) PRINT *,"Area is ", A PRINT *,"Circum. is ", C CONTAINS SUBROUTINE Rect(W,L,Area,Circ) REAL, INTENT(IN) :: W,L REAL, INTENT(OUT) :: Area,Circ Area = W*L Circ = 2*(W+L) END SUBROUTINE Rect END PROGRAM Rectangle

PROGRAM Rectangle IMPLICIT NONE REAL :: X,Y,A,C PRINT *,"Input the sides:" READ *,X,Y CALL Rect(X,Y,A,C) PRINT *,"Area is ",A PRINT *,"Circum. is ",C END PROGRAM Rectangle SUBROUTINE Rect(W,L,Area,Circ) REAL, INTENT(IN) :: W,L REAL, INTENT(OUT) :: Area,Circ Area = W*L Circ = 2*(W+L) END SUBROUTINE Rect

INTENT(IN) - means that the dummy argument is expected to have a value when the procedure is referenced, but that this value is not changed by the procedure.

INTENT(OUT) - means that the dummy argument has no value when the procedure is referenced, but that it will give one before the procedure finishes.

INTENT(INOUT) - means that the dummy argument has an initial value that will be updated by the procedure.

Ex: Write a program to read three positive numbers and use a single internal

subroutine to compute the arithmetic, geometric and harmonic means.

PROGRAM Mean6 IMPLICIT NONE REAL :: x, y, z REAL :: ArithMean, GeoMean, HarmMean READ(*,*) x, y, z CALL Means(x, y, z, ArithMean, GeoMean, HarmMean) PRINT*, "Arithmetic Mean = ", ArithMean PRINT*, "Geometric Mean = ", GeoMean PRINT*, "Harmonic Mean = ", HarmMean

Page 18: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

33

CONTAINS SUBROUTINE Means(a, b, c, Am, Gm, Hm) IMPLICIT NONE REAL, INTENT(IN) :: a, b, c REAL, INTENT(OUT) :: Am, Gm, Hm Am = (a + b + c)/3.0 Gm = (a * b * c)**(1.0/3.0) Hm = 3.0/(1.0/a + 1.0/b + 1.0/c) END SUBROUTINE Means END PROGRAM Mean6

Ex: Write a program uses Heron formula to compute the area of a triangle has side lengths a, b and c .

√ where s = (a+b+c)/2 The following two conditions must be satisfied : (a > 0 , b > 0 and c > 0) and ( a+b > c, a+c > b and b+c > a)

PROGRAM HeronFormula IMPLICIT NONE REAL :: a, b, c, TriangleArea LOGICAL :: x PRINT *, " Enter sides of a triangle " READ *, a, b, c x= TriangleTest(a, b, c) IF (x) THEN TriangleArea = Area(a, b, c) PRINT *, "Triangle area is " , TriangleArea ELSE PRINT *, "Your inputs cannot form a triangle." END IF

CONTAINS LOGICAL FUNCTION TriangleTest(a, b, c)

IMPLICIT NONE REAL, INTENT(IN) :: a, b, c LOGICAL :: test1, test2 test1 = (a > 0).AND.(b > 0).AND.(c > 0) test2 = ((a+b)>c) .AND. ((a+c)>b) .AND. ((b+c)>a) TriangleTest = test1 .AND. test2

END FUNCTION TriangleTest REAL FUNCTION Area(a, b, c)

IMPLICIT NONE REAL, INTENT(IN) :: a, b, c REAL :: s s = (a + b + c) / 2.0 Area = SQRT(s*(s-a)*(s-b)*(s-c))

END FUNCTION Area END PROGRAM HeronFormula

Page 19: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

34

Ex: Write a program to convert an octal number to decimal PROGRAM octal2decimal IMPLICIT NONE INTEGER :: oct, decimal READ*, oct decimal=octal(oct)

PRINT *, "The decimal of ",oct,"is ",decimal CONTAINS INTEGER function octal (z) INTEGER , INTENT(INOUT) :: z INTEGER :: R,m=0,sum=0 DO WHILE (z/=0) R=mod(z,10) sum=sum+(8**m)*R z=z/10 m=m+1

END DO octal=sum

END FUNCTION octal END PROGRAM octal2decimal

Page 20: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

35

6. Arrays and Matrices

An array is a group of variables or constants, all of the same type (integer, real, ….) which is referred to by a single name. Array elements are stored in an adjacent memory locations. Arrays are of two types:

1. One dimensional array.

2. Multi-dimensional array (matrices).

6.1 One Dimensional Array

The masses of a set of 5 objects can be represented by the array variable : Mass(5) ! an array of 5 elements of type real

Index 1 2 3 4 5 Mass 8.471 3.683 9.107 4.739 3.918

Element

The position of an element in array is called array index or subscript. Mass(1) = 8.471 Mass(2) = 3.683 Mass(3) = 9.107 Mass(4) = 4.739 Mass(5) = 3.918

The declaration of one dimensional array is done as illustrated below.

type , DIMENSION (number of elements in the array) :: name

OR type :: name(number of elements in the array)

for example:

INTEGER , DIMENSION(10) :: A ! Array A has 10 integers.

OR INTEGER :: A(10)

REAL , DIMENSION(20) :: B ! Array B has 20 real elements.

OR REAL :: B(20)

CHARACTER , DIMENSION(15) :: C ! Array C has 15 characters.

OR CHARACTER :: C(15)

LOGICAL , DIMENSION(5) :: D ! Array D has 5 logical elements.

Page 21: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

36

The index does not have to begin at 1, it can be zero or even negative; this is achieved with the ":" symbol:

REAL :: A(0:8), B(-4:4), C(-8:0)

All the above arrays have 9 elements. The index of A runs from 0 to 8, the index of B runs from -4 to 4 (including zero), and the index of C runs from -8 to 0. A One Dimensional Array can be initialized as follows:

A = (/ 4, -2, 6, 0, 1, 9, 1, -1, 6, 8 /)

A(1:4) = 0 ! the first four elements are 0. A(5:10) = 1 ! the last six elements are 1.

assigns to array A the values:

0 0 0 0 1 1 1 1 1 1

A = (/(I*0.1, I=1,10)/) ! using implied loop

assigns to array A the values: 0.1 0.2 0.3 0.4 0.5 0.6 0.7 0.8 0.9 1.0

6.2 Array Input/Output

Consider an array A declared as: REAL :: A(10) The input and of the array can be done as follows :

As a whole array : READ *, A

Using DO loop DO I=1, 10 READ *, A(I) END DO

Using an implied DO loops: READ *,(A(I),I=1,10)

There are various methods for the output of arrays; consider the array: REAL :: A(9) = (/(I*0.1, I = 1, 9)/)

The free-format output of the whole array PRINT *, A OR PRINT *, (A(I), I = 1, 9) gives : 0.1000000 0.2000000 0.3000000 0.4000000 0.5000000 0.6000000 0.7000000 0.8000000 0.9000000

A formatted output, for example: PRINT '(9(F3.1,1X))', A

Page 22: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

37

gives :

0.1 0.2 0.3 0.4 0.5 0.6 0.7 0.8 0.9

If the multiplier is omitted then the output will be given line by line; i.e. PRINT '(F3.1,1X)', A

This is equivalent to the DO loop: DO I = 1, 9

PRINT '(F3.1,1X)', A(I) END DO

gives: 0.1 0.2 0.3 0.4 0.5 0.6 0.7 0.8 0.9

Array sections can also be referenced, for example: PRINT '(7(F3.1,1X))', A(3:8) PRINT '(5(F3.1,1X))', A(1:9:2)

gives: 0.3 0.4 0.5 0.6 0.7 0.8

0.1 0.3 0.5 0.7 0.9

Set an array element to its index or subscript. INTEGER, PARAMETER :: BOUND = 20 INTEGER, DIMENSION(1:BOUND) :: Array INTEGER :: i DO i = 1, BOUND Array(i) = i END DO

Page 23: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

83

6.3 Two/Multi-dimensional arrays Although it is useful to have data in one-dimensional arrays, it is

sometimes useful to arrange data into rows and columns (two dimensional arrays), rows, columns, and ranks (three-dimensional), or even higher dimensionality. In this section we will consider multidimensional arrays.

Two dimensional arrays are the most common and the subscripts are just as indicated in most math textbooks. The first subscript represents row number, and the second column number. Consider the matrix A(n,m) :

A(1,1) A(1,2) . . . A(1,m)

A(2,1) A(2,2) . . . A(2,m)

......

A(n,1) A(n,2) . . . A(n,m)

Multi-dimensional arrays are declared in much the same way as single arrays. In general, for n-dimensional arrays:

type :: array_name (num. of rows, num. of columns, num. of ranks, ….)

A two-dimensional array can be declared as follows:

type :: array_name (num. of rows , num. of columns)

For example:

INTEGER, DIMENSION(3,4) :: B,C ! B and C are 3x4

REAL, DIMENSION(0:4,3:12,5) :: A !A is a 5x10x 5

REAL :: A(4,10,5)

INTEGER :: B(1:3 , 1:5) LOGICAL :: D(-1:4, 0:5)

6.4 Input/Output of Two-Dimensional Array Two-dimensional arrays can be read using: the array name without subscripts, explicit DO loops, and implied DO loops.

The array name without subscripts: All the values in A are read in column order A(1,1), A(2,1), ….. , A(n,1), A(1,2), A(2,2)…… , etc.

READ *, A

Page 24: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

83

Explicit DO loops : nested DO loops are required as follows:

For "row-wise" input: the elements of the first row is read, then the second row, then third, etc. until completed.

DO i = 1, n

DO j = 1, m

READ *, A(i, j)

END DO

END DO

For "Column-wise" input : In this case, the elements of the first column is read, then the second column, then third, etc.

DO j = 1, m

DO i = 1, n

READ *, A(i, j)

END DO

END DO Implied DO loops :

For "row-wise" input: READ *, ((A(i,j), j = 1, m), i = 1, n)

For "Column-wise" input READ *, ((A(i,j), i = 1, n), j = 1, m)

To print the matrix A(m,n) , this can be done using a combination of DO loops and implied DO loops as follows:

DO I = 1,m

PRINT *, (A(I,J), J=1,n)

END DO

The output is :

A(1,1) A(1,2) A(1,3) …… A(1,n) A(2,1) A(2,2) A(2,3) …… A(2,n)

.

. A(m,1) A(m,2) A(m,3) …… A(m,n)

For example: to print the matrix

Page 25: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

04

DO i = 1, 3

PRINT '(1x,4I5)',(A(i,j),j=1,4)

END DO

The output is :

1 2 3 4 5 6 7 8 9 1 2 3

DO i = 1, 3

PRINT '(1x,4I2)',(A(i,j),j=1,4)

END DO

The output is :

1 2 3 4 5 6 7 8 9 1 2 3

6.5 Sections of Arrays Accessing a section of an array requires the upper and lower bounds of

the section to be specified together with a step (for each dimension). for example:

REAL, DIMENSION(8) :: a INTEGER, DIMENSION(5,4) :: b

REAL, DIMENSION(6) :: c INTEGER, DIMENSION(4,5) :: d a(3:5) !elements 3, 4, 5 a(1:5:2) !elements 1, 3, 5 b(1:2,2:3) !elements (1,2) (2,2) (1,3) and (2,3) b(3,1:4:2) !elements 1 and 3 of the third row b(2:4,1) !elements 2, 3 and 4 of the first column c(:) !whole array

c(:3) !elements 0,1,2,3 c(::2) !elements 0,2 and 4

d(:,4) !all elements of the fourth column. d(::2,:) !all elements of every other row

Ex: Write a program to find the average of the even and odd numbers in an array of 50 real numbers.

Page 26: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

04

PROGRAM AV_ODD_EVEN IMPLICIT NONE INTEGER, DIMENSION(50) :: A INTEGER :: i, countodd=0, counteven=0 REAL :: sumodd=0.0, sumeven=0.0 ,avo, ave READ *, (A(i), i = 1, 50) DO i=1,50 IF (MOD(A(i),2)==0)THEN sumeven=sumeven+A(i) counteven=counteven+1 ELSE

sumodd=sumodd+A(i) countodd=countodd+1 END IF END DO ave=sumeven/counteven avo=sumodd/countodd PRINT *, "Number of even numbers = " ,counteven PRINT *, "Sum of even numbers = " ,sumeven PRINT *, "Average of even numbers = " ,ave PRINT *, "Number of odd numbers = " ,countodd PRINT *, "Sum of odd numbers = " ,sumodd PRINT *, "Average of odd numbers = " ,avo END PROGRAM AV_ODD_EVEN

Ex: Write a program reads a set of real values and uses the following formulas to compute the mean, variance and standard deviation (use subroutine).

∑ √

PROGRAM Mean_Variance_StdDev IMPLICIT NONE INTEGER :: n, i READ *, n REAL, DIMENSION(n) :: data ! input array REAL :: Mean, Variance, StdDev ! results PRINT *, "Input data:" READ *, (data(i), i = 1, n) CALL M_V_SD (data, n, Mean, Variance, StdDev) PRINT *, "Mean : ", Mean PRINT *, "Variance : ", Variance PRINT *, "Standard Deviation : ", StdDev CONTAINS SUBROUTINE M_V_SD(d, n, M, V, SD)

IMPLICIT NONE INTEGER, INTENT(IN):: n REAL, DIMENSION(1:n),INTENT(IN) :: d REAL, INTENT(OUT):: M, V, SD REAL :: sum1=0.0, sum2=0.0 ! compute Mean

Page 27: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

04

DO i = 1, n sum1 = sum1+d(i) END DO M = sum1/n ! compute variance DO i = 1, n sum2=sum2+(d(i)-M)**2 END DO V= sum2/(n-1) ! compute standard deviation SD = SQRT(V) END SUBROUTINE M_V_SD END PROGRAM Mean_Variance_StdDev

Ex: Write a program that reverses the order of the elements of a given array.

PROGRAM Reverse IMPLICIT NONE INTEGER, PARAMETER :: SIZE = 30 INTEGER, DIMENSION(1:SIZE) :: a INTEGER :: n,m, Temp, i READ *, n PRINT *, "Input an array:" READ *, (a(i), i = 1, n) m=n DO i=1, n/2 Temp = a(i) a(i) = a(m) a(m) = Temp m=m-1 END DO PRINT *, "The Reversed array:" PRINT *, (a(i), i = 1, n) END PROGRAM Reverse

Ex: Write a program reads an array of 100 elements and finds the maximum elements.

PROGRAM maximum IMPLICIT NONE REAL :: a(100) INTEGER :: i , Max PRINT *, "Input an array:" READ *, (a(i), i = 1, 100) Max=a(1) DO i=2,100 IF (a(i)>max) THEN Max=a(i)

END IF END DO PRINT *, "maximum=" ,Max END PROGRAM maximum

Ex: Write a program to sort an array of 10 integers in an ascending order.

Page 28: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

08

PROGRAM SORT IMPLICIT NONE REAL :: a(10),temp INTEGER :: i, j PRINT *, "Input the array:" READ *, (a(i), i = 1, 10) outer: DO i=1,9 inner: DO j=i+1,10 IF (a(i)>a(j)) THEN temp=a(i) a(i)=a(j) a(j)=temp END IF END DO inner END DO outer PRINT *, (a(i), i = 1, 10)

END PROGRAM SORT

Ex: Write a program reads two matrices 10x10 and finds the sum and difference of them.

PROGRAM SUM_DIFF IMPLICIT NONE REAL, DIMENSION(10,10) :: A , B, C, D INTEGER :: i,j READ *, ((A(i,j), j = 1, 10), i = 1, 10) READ *, ((B(i,j), j = 1, 10), i = 1, 10) Do i=1,10 DO j=1,10 C(i,j)=A(i,j)+B(i,j) D(i,j)=A(i,j)-B(i,j) END DO

END DO DO i = 1,10

PRINT *, (C(i,j), j=1,10) END DO DO i = 1,10

PRINT *, (D(i,j), j=1,10) END DO

END PROGRAM SUM_DIFF

Ex: Write a program to find the product of two matrices A[3][3] and B[3][3].

PROGRAM PRODUCT IMPLICIT NONE REAL, DIMENSION(3,3) :: A , B, C, INTEGER :: i,j,k READ *, ((A(i,j), j = 1, 3), i = 1, 3) READ *, ((B(i,j), j = 1, 3), i = 1, 3)

Page 29: 3. Repetitive Structures (Loops)

FORTRAN 90 LECTURES ABDUL-MUTTALIB. A. H. AL-DOURI

00

C(3,3)=0 outer: Do i=1,3 middle: DO j=1:3

inner: DO k=1:3 C(i, j)= C(i, j)+A(i, k)+B(k, j) END DO inner END DO middle

END DO outer DO i = 1,3

PRINT *, (C(i, j), j=1,3) END DO

END PROGRAM PRODUCT

Ex: Write a program reads a matrix A[4][4] of real numbers, and then generates an array of four elements, the first element is the sum of the diagonal elements of the matrix, the second is the sum of the upper triangular elements, the third is the sum of the lower triangular elements, and the forth is the sum of the secondary diagonal elements.

PROGRAM ARRAY_GENERATION IMPLICIT NONE REAL, DIMENSION(4,4) :: A REAL :: B(1:4)=0 INTEGER :: i,j READ *, ((A(i,j), j = 1, 4), i = 1, 4) DO i=1,4 DO j=1,4 IF(i=j) THEN B(1)=B(1)+A(i,j)

ELSEIF (i<j) THEN B(2)=B(2)+A(i,j)

ELSE B(3)=B(3)+ A(i,j)

END DO B(4)=B(4)+ A(i,4+1-i)

END DO PRINT *, (B(i), i=1,4)

END PROGRAM ARRAY_GENERATION

H.W Write a program reads three arrays of real numbers, and generate an array of three elements each element represents the maximum element of each array. The program calls an external function receives an array and returns the maximum element.