Sie sind auf Seite 1von 19

USER GUIDE FOR FORTRAN 90/95

Chemical Engineering Department, Middle East Technical University

2012

Course: ChE 352, Mathematical Modelling in Chemical Engineering


Instructor: Prof.Dr. Nevin Seluk
Assistant: Necip Berker ner

1) Introduction
FORTRAN is the oldest programming language, developed in 1957. It is renewed many times and the
latest version is FORTRAN 2008. FORTRAN set the foundations of scientific computing with the version 77
and it is still the most widely used scientific language, due to its computing speed and extensive libraries
on the internet (subprograms, see Chapter 7). This course will use the FORTRAN 95 edition, which is the
upgraded version of 77 and includes some extensions to the 90 version.

a) Execution of a Program
Execution involves several steps. After establishing an algorithm, the source code is written with a
text editor. Then compiler software translates the code into a machine code. Finally the code is
executed. For compiling we will use the Silverfrost Plato FTN95 Personal Edition software, which is free
and can be downloaded from:
http://www.silverfrost.com/32/ftn95/ftn95_personal_edition.aspx .
Another option is Force 2.0. But it is not compatible with some of the new pcs.
-

Plato FTN95
This compiler can create different formats of file. The ones that we are going to use is the free
format files with .f95 extension. The old 77 format is named as the fixed format which restricts
the programmer with paragraphs at the beginning of each row and a maximum row length of 66
characters. The free format is like a text file with no paragraph requirement and a maximum row
length of 128 characters. Figure 1 shows the interface of the program.

b) Notes on Code Writing

Use spaces and indentation to make the code readable


Use explanations, or in programming terminology: comments (explained in chapter 3), to
make the code understandable.

Program Tab. Multiple tabs


can be opened.

Compiler Setup. Checkmate is the


default. Slower but safer.

The Build Toolbar. The first three buttons represent compile,


build and execute. Build function generates an .exe file,
which is a midstep between compiling and execution.
Execute button also automatically compiles.

Figure 1. FTN95 Interface


Text code. Commands in blue, values and variables in black,
operative symbols in red and comments are in green.

Line and column numbers.

Compiling log. Shows errors and warnings after compiling and


building.

2) General Code Layout


i)
ii)
iii)
iv)

Program Name
Type Declarations (Chapter 3)
File Management (Chapter 8)
Initialization & Input (Chapter 3)

v)
vi)
vii)
viii)

Main Calculations
Output (Chapter 8)
End
Subprograms & Functions (Chapter 7)

3) Types, Variables, Constants, Operators


a) Starting and ending the program
With the PROGRAM name command, the program starts. name is the given title of the
program. This command is not necessary. Its use can be seen in Figure 1. The code must be finalized
by END statement. In part d, an example is shown.
b) Variable Names

Composed of letters and/or digits and/or underscores,


No longer than 31 characters,
First character must be a letter,
Names are case insensitive!

c) Variable Types
There are 6 intrinsic1 types in FORTRAN, which are integer, real, double precision, complex, logical,
and character. The first four is important for us. These define the value of a variable. There are also
derived types and adjusted precision, which are out of the scope of this tutorial.
-

Integer Type: stores values without decimals; for example :32, 49802,-9
Real Type: stores values with 5 decimals, rounds the 6th decimal up or down; for example:
-45.23043
Double Precision: stores values with 11 decimals; rounds the 12th decimal up or down for
example: -45.23043778221. (In this course always use DOUBLE PRECISION instead of REAL!)
Character: stores a text instead of values; for example: root or root.

Anything which has pre-defined attributes in FORTRAN.

These commands constitute the type decleration part. They are used as in the following context2:

INTEGER :: ITERATION, NUM


REAL :: RESULT, R_OLD
DOUBLE PRECISION :: COEFFICIENT1, COEFFICIENT2
CHARACTER(LEN=5) :: LINE
The LEN statement defines the maximum string length. Values may be given to these variables such as:
NUM = 1
R_OLD = 5.67
COEFFICIENT1 = 240.5
LINE = Mark
Note that the character strings are written in quotes ( or ).
d) Implicit Statements and the PARAMETER Command
In FORTRAN all variables starting with i, j, k, l, m or n are considered as integer and the remaining is
real. To remove this intrinsic definition, one can write the following commands at any row of the code,
but preferentially at the beginning, after the PROGRAM statement:
IMPLICIT NONE
IMPLICIT DOUBLE PRECISION (A-H,O-Z)
The first code removes all available definitions. After this code type of every variable must be declared.
The second code shows an example of giving certain character intervals to a type of variables.
The PARAMETER command serve for defining the value of a constant. The command can be
placed above the type declaration block.
REAL, PARAMETER :: PI = 3.14159
e) Arithmetic Operations, Simple Input & Output
Basic operators are used as they are, such as +,-,* and /. But for exponentiation ** is used instead of
^. The mathematical precedence of the operators is important in FORTRAN since all equations are
written is a linear form. For example:
(

corresponds to 4 * (3 + 7)-2**4/2, yields 4 * 10 16 / 2 and thus 32.

REAL and DOUBLE PRECISION can also be defined as REAL(KIND=1) and REAL(KIND=2). REAL(KIND=3) is another
definition which allows 16 decimals, rounded after the 17th.

For multiple exponentiations, there is an exception.

is written as 3**2**3, and it is evaluated from right to left.


Integer divisions need some special care. Integer to integer division will give an integer result and
inexact division cause a loss of precision since integers do not have decimals. For example:
PROGRAM TEST
INTEGER :: A,B
REAL :: C,D,RES1,RES2
PRINT*,"INPUT A"
READ*, A
B=3
C=7 ;D=3
RES1 = A/B
RES2 = C/D
PRINT*, "RES1=", RES1,"RES2=", RES2
END PROGRAM TEST
The READ*, statement is a basic input command and the PRINT*, command is its counterpart for
output. The value of A is given during execution via the READ statement. PRINT statement displays the
values of variables in the monitor after execution. As seen from the rows 4 and 10, it can output texts
also. Note that the semicolon operator allows multiple statements per row. When this program is run,
the execution screen comes up as:

Figure 2. The Execution Screen

Integer division leads to different values. But any operation between a real and an integer
variable lead a real result. To avoid integer division, the decimal point can be put after integers, such as
A = 3./7
f)

instead of

A = 3/7

Logical and Relational Operators

These are used in conditional statements, such as the IF commands. The important logical
operators are:
.NOT. .AND. .OR.
5

The relational operators are renewed in F90; textual operators such as .GT. (greater than) are
replaced with:
<

less than

<=

less than or equal to

>

greater than

>=

greater or equal to

==

equal to

/=

not equal to

g) Intrinsic Functions
There are lots of mathematical and non-mathematical functions in F90. The most important ones
may be listed as:
SIN(X)
LOG(X)
LOG10(X)
EXP(X)
ABS(X)
SQRT(X)

Sine function. Other trigonometric functions are available and similarly used.
Natural logarithm function
Logarithm function with the base of ten (common logarithm)
Exponential function
Absolute value of the numerical argument X
Square root function

h) Comments and Continuation Lines


The exclamation mark ! can be used to input comments. Anything written after ! will be
considered as a comment in FORTRAN. These comments can also be used on the same row with
statements. The usage of ! can be seen in Figure 1.
If a statement is too long to fit in 128 characters, then the & mark is added to the end of the line, and
then the continuing part of the statement is written on the next line. For example
C = SQRT(A ** 2 + B ** 2 - &
2 * A * B * cos(alpha))
which is equal to:
C = SQRT(A ** 2 + B ** 2 - 2 * A * B * cos(alpha))
*From now on the chapters will be explained via examples.

4) IF Statements
Frequently used with GO TO statement.

Example-4.1: Write a program to find the sum of even numbers between two integers
PROGRAM EVEN_SUM
INTEGER :: ESUM,NUMLOW,NUMHIGH
!

The lowest and highest numbers

PRINT*,"INPUT THE LOWEST NUMBER"


READ*, NUMLOW
PRINT*,"INPUT THE HIGHEST NUMBER"
READ*, NUMHIGH
Check if NUMLOW is even
IF(MOD(NUMLOW,2)==1) NUMLOW=NUMLOW+1

10

IF loop to find the sum


ESUM=0
ESUM=ESUM+NUMLOW
NUMLOW=NUMLOW+2
IF(NUMLOW<=NUMHIGH) GO TO 10
Output
PRINT*, "SUM OF EVEN NUMBERS IS:", ESUM
END PROGRAM EVEN_SUM

The example above demonstrates the two way conditioning with the basic combination of IF and
GO TO statements. Note the use of MOD intrinsic function, which calculates the remainder of the integer
division of NUMLOW by 2. If the outcome of an conditional statement is multiple, then IF blocks should
be used. An example is shown below.
Example-4.2: Write a program to input three coefficients of the quadratic equation

and find and print the possible real roots using the block IF structure.
PROGRAM QUADRATIC_ROOTS
IMPLICIT NONE
REAL :: A, B, C, D, X, X1, X2

The coefficients

10

READ*, A, B, C
PRINT*,'INPUT COEFFICIENTS ARE:', A, B, C

The discriminant: D
D=B**2-4*A*C
PRINT*, D

IF-THEN-ELSE structure
IF(A<=0.0) THEN
STOP
ELSE IF(D<0) THEN
PRINT*, 'NO REAL ROOTS EXISTS'
ELSE IF(ABS(D)<1E-5) THEN
X=-B/(2*A)
PRINT*,'ONE REAL ROOT EXISTS AND IT IS:',X
ELSE
X1=(-B-SQRT(D))/(2*A)
X2=(-B+SQRT(D))/(2*A)
PRINT*,'TWO REAL ROOTS EXISTS AND THEY ARE',X1,X2
ENDIF
GO TO 10
END PROGRAM QUADRATIC_ROOTS

Note that the discriminant is not zero for coincident roots. That line only shows an interval
between -10-5 and 10-5. The reason is, in Plato, comparing floating point quantities3 may be erroneous.
Although the precision of the variables are set to 5 numbers after the decimal, Plato stores more than
that. Hence, it may print the real variable D as 0.00000 but when comparing it to an actual zero, it may
not be equal (Computers are not always exact.). Since the accuracy after 10-5 is not necessary for this
example, setting an interval is a practical solution.
An IF block starts with a regular IF statement and continues with the THEN statement. After this
condition, each IF statement includes a relational or logical condition with ELSE IF and the THEN
statement, except the last condition is only comprised of ELSE. The block should be ended with ENDIF.
When multiple IF blocks are used, special care must be taken to place the blocks in each other. The first
(the outer) block must have its ENDIF statement at the end.
The STOP statement can be used to terminate the program at specific points, as can be seen from
first IF of the IF-THEN-ELSE structure.
3

Values with decimals.

5) DO Loops
DO loops are useful when recycling a part of the code for different cases and variables. A basic example
is shown below.

Example -5.1: Rewrite Example 4.1 with using DO loops.


PROGRAM EVEN_SUM_II
INTEGER :: ESUM,NUMLOW,NUMHIGH,LOWBOUN
!

The lowest and highest numbers


PRINT*,"INPUT THE LOWEST NUMBER"
READ*, NUMLOW
PRINT*,"INPUT THE HIGHEST NUMBER"
READ*, NUMHIGH

Check if NUMLOW is even


IF(MOD(NUMLOW, 2)==1) NUMLOW=NUMLOW+1

Do loop to find the sum


ESUM=0
DO I= NUMLOW, NUMHIGH, 2
ESUM=ESUM+I
ENDDO

Output
PRINT*, "SUM OF EVEN NUMBERS IS:", ESUM
END PROGRAM EVEN_SUM_II

I is the counter for the DO loop. It starts from the lowest number, then the below commands
are performed. The ENDDO statements works as the lines
NUMLOW=NUMLOW+2
IF(NUMLOW<=NUMHIGH) GO TO 10
in Example-4.1. It increases I by the amount of 2, and continues to perform the loop until I NUMHIGH.
Thus the DO statement provides an easy way of performing loops. The next example shows the way of
using nested loops.

Example-5.2: Evaluate the power series of ex

For the x values -1.0, -0.5, 0, 0.5, 1 by using the first 10 terms of the series for each value of x.

PROGRAM POWEREXP
DOUBLE PRECISION :: X,EXPX,TERM,FACT

GENERATE THE X VALUES


DO X= -1.0, 1.0, 0.5

Calculate the e^x using the first 10 terms


EXPX=1+X
DO ITERM=2, 9

The factorial of a term


FACT=1
DO M=ITERM, 1, -1
FACT=FACT*M
ENDDO

Compute the term and add it to the sum


TERM=X**ITERM/FACT
EXPX=EXPX+TERM
ENDDO

Print out the result for an x value and cycle


PRINT*,X,EXPX,EXP(X)
ENDDO
END PROGRAM POWEREXP

The DO loops counter is X and it is incremented by 0.5, starting from -1.0 and ending at 1.0.
During lectures, some extensions to this chapter, such as endless DO loops, the EXIT command and CASE
constructs will be demonstrated.

10

6) Arrays
An array means a set of variables with subscripts. For example a 1-D array stand for a vector and
a 2-D array represents a matrix. In engineering context a maximum of 4-D arrays are used. Fortran 95 is
limited to 7-D. Arrays are declared similar in a similar way to single variables.
REAL :: VECT(5)
INTEGER :: AMATRIX(3,4)
DOUBLE PRECISION :: BLOCK(0:8,-30:10)
The type of the elements of an array must be declared. The first array consists of 5 real elements. The
first element is designated as VECT(1) and the last one is VECT(5). The second one is a matrix with 3 rows
and 4 columns. The element on the 2nd row and 4th column is shown as AMATRIX(2,4). The third array is
an example of adjustable bounds. It is also a 2d matrix with 9 rows, starting from the 0th and ending at
the 8th. Similarly it has 41 columns. The element in the middle is designated as BLOCK(4,-10).

Example-6.1: Write a program to evaluate the polynomial expression

for given values of n, a1, a2, , an using various values of x which are read in . Let the program terminate
when a zero value of x is read in. The program can be limited to n 25. Use the Horners method, which
is based on the nesting:

((

PROGRAM POLYNOMIAL_EVALUATION
REAL :: A(25),POLY,X
!

10

Input the order, the coefficients and X


READ*, N, (A(J),J=1, N)
READ*, X
IF (X==0) THEN
PRINT*,"F(X)=",A(N),"WHEN X=0"
STOP
ENDIF
Horner's Method
POLY=A(1)
DO I=2, N
POLY=POLY*X+A(I)
ENDDO
11

PRINT*,"F(X)=",POLY,"WHEN X=",X
GO TO 10
END PROGRAM POLYNOMIAL_EVALUATION

The READ statement on line 6 is written an implied DO structure. First N, then every element of
the array A is read in one line.

Example-6.2: Write a program to take the transpose of any matrix.


PROGRAM TRANSPOSITION
REAL, ALLOCATABLE, DIMENSION (:,:) :: M,MT
!

Input the number of rows & columns

READ*, I, J
Allocate the matrix size
ALLOCATE (M(I,J),MT(J,I))

Read the values and print the matrix


READ*, ((M(K,L),L=1,J),K=1,I)
DO K=1,I
PRINT*,(M(K,L),L=1,J)
ENDDO

Transposition
DO K=1,J
DO L=1,I
MT(K,L)=M(L,K)
ENDDO
ENDDO
PRINT*,' '

Output
DO L=1,J
PRINT*,(MT(L,K),K=1,I)
ENDDO
END PROGRAM TRANSPOSITION

12

In this example allocatable arrays are used. In Example-6.1, we assumed a maximum size of the
array. In this code, the size can be adjusted on each time we run the program. Simple DO loops and
implied DO loops (nested & implied on line 14) are used to create a neat input-output structure.
As seen in the examples of this chapter, using DO loops is very important in automatically
assigning values to array elements. There is also the DATA statement which allows this in a semi-manual
manner, but it will not be explained here.

7) Functions and Subroutines


Some programs may need a block of computations to be repeated. Writing the same of block of
computation more than once generally makes the program hard to read and trace. In such a case, the
computation can be written as a subprogram and can be placed outside of the main code. The main code
can call the subprogram and make it work for different sets of variables.
Another reason for using subprograms is to create a certain library of basic computations, which
are used repeatedly in the working field of the programmer. Once a library of subprograms is
established, the programmer can write any new relevant code faster.
There are two types of subprograms: functions and subroutines. Their examples are given below.

Example-7.1: Write a program which calculates the area of a triangle when the side lengths of a triangle
are given. Use a FUNCTION type subprogram.
PROGRAM AREA_TRIANGLE_SIDES
PRINT*, 'INPUT THE SIDE LENGHTS'
READ*, X, Y, Z
!

Build a checking mechanism to stop the program if negative side lengths are given
IF((X<=0).OR.(Y<=0).OR.(Z<=0)) STOP

Call the function & output the results


A=AREA(X, Y, Z)
IF(A<=0) THEN
PRINT*, 'NO SUCH TRIANGLE EXISTS'
ELSE
PRINT*, 'THE AREA IS:', A
ENDIF
END PROGRAM AREA_TRIANGLE_SIDES

13

!-------- Subprogram for calculating the area of the triangle from side lengths
REAL FUNCTION AREA(A, B, C)
AREA=0
!

Check the existence of the triangle


IF(A>=B+C) RETURN
IF(B>=A+C) RETURN
IF(C>=A+B) RETURN

Find the area if the triangle exists


S=0.5*(A+B+C)
AREA=SQRT(S*(S-A)*(S-B)*(S-C))
END

Line 8 demonstrates the use of multiple logical operators. The RETURN command works like the
STOP command in a main program.
The subprograms structure is the same with the main program. It starts with the FUNCTION
command, then involves computations and terminates with END. It might have type declaration lines
after the FUNCTION statement, but in this case, all variables (A, B, C, AREA and S) are predefined as real.
Note that the dummy arguments of the function AREA, which are A, B and C, do not have to have the
same names used in program; X, Y and Z. Only their order is important, in this case, X corresponds to A, Y
and Z correspond similarly to B and C respectively. In a FUNCTION type subprogram the name of the
function must have a value assigned, since only its value is sent to the main program. The dummy
variables are terminated after the subprogram is executed. Remember that the dummy variables cannot
be chosen as array elements. Also note that the type of the function name is declared since it has a value
assigned.

Example-7.2: Write a program to calculate the average of a real array, having maximum 100 elements.
Use a SUBROUTINE type subprogram.

10

PROGRAM AVERAGE_ARRAY
REAL :: A(100),MEAN
WRITE(*,*) 'INPUT ARRAY SIZE, K:'
READ*, K

Check the array size


IF(K>=100) THEN
WRITE(*,*) 'ARRAY SIZE IS LIMITED TO 100, RE-INPUT K:'
GO TO 10
ENDIF
14

Input the array elements


READ*, (A(I), I=1,K)

Call the subroutine to find the average


CALL AVE(MEAN,K,A)
WRITE(*,*) 'THE AVERAGE IS:',MEAN
END

!--------Subroutine for finding the average of a 1-D array of max. 100 elements
SUBROUTINE AVE(MEAN,N,A)
REAL ::A(100),MEAN
SUM=0
DO I=1,N
SUM=SUM+A(I)
ENDDO
MEAN=SUM/N
END
The SUBROUTINE type subprogram is quite different than the FUNCTION type. Its name does not
have value assigned, all of it variables are processed and their values are kept in the main program. It
needs the CALL statement in the main program to work. SUBROUTINEs are more capable then
FUNCTIONs, hence they are more frequently used.
Instead of PRINT command, WRITE command is used here. It does the same job in this program,
but normally it is more capable. It will be treated in detail in Chapter 8.

Example-7.3: Write a program to evaluate

numerically with trapezoidal integration


[( )

( )
where

) )

( )]

15

PROGRAM TRAPEZOIDAL
EXTERNAL FX1,FX2
!

Input n
PRINT*,'INPUT THE NUMBER OF INTERVALS'
READ*, N

Approximate the integral


APPROXINT=TRAPEZ(FX1,0.1,0.5,N)+TRAPEZ(FX2,0.0,0.4,N)
PRINT*,'THE APPROXIMATE AREA IS:', APPROXINT
END PROGRAM TRAPEZOIDAL

!-------- Subprogram to calculate (sin(x))^2


FUNCTION FX1(X)
FX1=(SIN(X))**2
END
!-------- Subprogram to calculate (cos(x))^2
FUNCTION FX2(X)
FX2=(COS(X))**2
END
!-------- Subprogram to find the integral of a function with the trapezoidal rule
FUNCTION TRAPEZ(FX,A,B,N)
H=(B-A)/N
SUM=0
J=N-1
DO I=1,J
SUM=SUM+FX(A+I*H)
ENDDO
TRAPEZ=(FX(A)+FX(B)+SUM*2)*(H/2)
END

This program demonstrates the linking of subprograms with the EXTERNAL statement. Since
FUNCTION TRAPEZ uses FX1 and FX2, two subprograms, as dummy variables, the main program must be
acknowledged.

16

Subprograms are an important part of programming. In FORTRAN there are many other
commands and principles related to subprograms such as EQUIVALENCE, COMMON, BLOCK DATA,
INTERNAL, INTRINSIC, ENTRY, INTENT, RECURSIVE and many more.

8) Files and Formatted Output


For a neat and processable output, files and formatted output must be used. Since both file management
and formats are broad topics, only the basic use of them will be demonstrated through an example.

Example-8.1: Write a program to calculate the factorial n! using both the standard method and Stirlings
approximation:
(

Tabulate the results.


PROGRAM FACTORIAL
INTEGER :: STANDARD
!

Open the output file and input the factorial limit


OPEN(5,FILE="Factorial Sheet.txt",STATUS="REPLACE")
WRITE(5,10) "Numbers", "Standard Results", "Stirling's Results", "Relative Percent Error"
READ*, N

Use the functions and create the output file


DO I=1, N
STANDARD=IFACT(I)
STIRLING=FACTST(I)
ERR=ABS(STIRLING-STANDARD)/STANDARD*100
WRITE(5,20) I,STANDARD,STIRLING,ERR
ENDDO

Output formats

10
20

FORMAT(A10, 3(A24))
FORMAT(I10, I24, 2(F24.5))
END PROGRAM FACTORIAL

!-------- Subprogram to calculate a factorial


INTEGER FUNCTION IFACT(N)
IPROD=1
IFACT=1
17

IF(N<=1) GO TO 50
DO I=2, N
IPROD=IPROD*I
ENDDO
IFACT=IPROD
50
END
!-------- Subprogram to approximate a factorial by using Stirling's formula
REAL FUNCTION FACTST(N)
TERM1=SQRT(2*3.14159)
TERM2=FLOAT(N)**(FLOAT(N)+0.5)
TERM3=EXP(-FLOAT(N))
FACTST=TERM1*TERM2*TERM3
END

The result is tabulated in Table 1.


Table 1: Table of Factorials

A DO loop is used to print the output row by row. The intrinsic function FLOAT is there to convert
integers into reals.
The OPEN statement creates a text file named Factorial Sheet with the .txt format and
numbers it as 5. This number is used by WRITE statements. Remember that in Example 7.2 WRITE(*,*)
command is used. The first star means that the output will be given on the black execution screen (not
on any file) and the second one indicates that the output format is the default one used by the
unformatted PRINT*, command. In this example each WRITE statement has 2 numbers; first one is 5,
the number of the opened file. The second one is either 10 or 20, indicating the numbers of FORMAT
statements. For file numbering, use positive integers except 1 and 2.
At the beginning, the titles of the table columns are printed on the file (line 7, the first WRITE
statement). There are four texts and they are written by using the FORMAT statement numbered as 10.
Note that FORMAT statements have some letters inside their parentheses. A is for writing character
variables or texts, I is for writing integers and F is for real and double precision variables. The
numbers after A and I show the number of spaces (a blank made by the space button in a text editor)
that the variable is written on. The values are always right adjusted. However, there are two numbers

18

after F. The first one is the space indicator and the second one the number of decimals displayed. For
example with F5.3 will display 3.14159 as 3.141 since the decimal point also takes up a space.,
Writing the output on a file is important, since it allows processing of the data. The data on files
can be read by a graphing program, such as Tecplot, ParaView or even EXCEL, to create diagrams and
plots. For example, after running Example 8.1, a plot of the relative percent error can be drawn to
visualize its continuously decreasing trend.

9) Epilogue
For FORTRAN programming, many books and e-books are available. Many of them include
exercises of applying numerical methods. Although programming and numerical methods has diverse
context, the basic tools given in this tutorial is sufficient for solving many engineering problems
numerically.

References:
[1] van Mourik T., Fortran 90/95 Programming Manual, University College London, 2002.
E-Book is available and free.
[2] Page C., Fortran 90 for Fortran 77 Programmers, 2002
E-Book is available and free.
[3] Tokdemir F., Programming with FORTRAN77, ODT-Ankara, 1990.
[4] REAs Problem Solvers: Numerical Analysis, (Dir. by M. Fogiel), Revised Edition, Research &
Education Association, 1993.

19

Das könnte Ihnen auch gefallen