Sunteți pe pagina 1din 21

BASKOM-5 (YAKNI IDRIS) 1

In real programs we often need to handle a large amount of data in


the same way, e.g. to find the mean of a set of numbers, or to sort a
list of numbers or names, or to analyse a set of students' test
results, or to solve a system of linear equations.
Introduction to ARRAYS
To avoid an enormously clumsy program, where perhaps hundreds
of variable names are needed, we can use subscripted variables, or
arrays.
These may be regarded as variables with components, rather like
vectors or matrices.
They are written in the normal way, except that the subscripts are
enclosed in parentheses after the variable name, e.g. X(3), Y(I + 2 *
N)
BASKOM-5 (YAKNI IDRIS) 2
X
N
X
i
i
N

1
1
To illustrate the basic principles, let's compute the sample mean and
standard deviation of a set of N observations. The mean is defined as
where Xi is the ith observation. The standard deviation (s) is defined as

s
N
X X
i
i
N
2
2
1
1
1

Mean and Standard Deviation


BASKOM-5 (YAKNI IDRIS) 3
IMPLICIT NONE

INTEGER :: I, N
REAL :: Std = 0
REAL, DIMENSION(100) :: X
REAL :: XBar = 0

OPEN (1, FILE = 'DATA')

READ (1, *) N
DO I = 1, N
READ (1, *) X(I)
XBar = Xbar + X(I)
END DO

XBar = XBar / N

DO I = 1, N
Std = Std + (X(I) - XBar) ** 2
END DO

Std = SQRT( Std / (N - 1) )
PRINT*, 'Mean: ', XBar
PRINT*, 'Std deviation: ', Std
END
Try this with some sample data (each
number on a separate line):
10 5.1 6.2 5.7 3.5 9.9 1.2 7.6 5.3 8.7 4.4
You should get a mean of 5.76 and a
standard deviation of 2.53 (to two decimal
places).
BASKOM-5 (YAKNI IDRIS) 4
The DIMENSION(100) attribute in the type declaration statement for the array X sets
aside 100 memory locations, with names X(1), X(2), ..., X(100). However, the sample data
above consists of only 10 numbers, so only the first 10 locations are used. Note that the
value of N must be read first (and must be correct), before the N values may be read.
After the READ is complete, the memory area where the array is stored looks like this:

X(1) X(2) X(3) ... X(10)
5.1 6.2 5.7 ... 4.4
Now that the data are safely stored in the array, they may be used again, simply by
referencing the array name X with an element number, e.g. X(3). So the sum of the first
two elements may be computed as

SUM = X(1) + X(2)


This facility is necessary for computing s according to the formula abovethe data must
all be read to compute the mean, and the mean must be computed before all the data is
re-used to compute s.
BASKOM-5 (YAKNI IDRIS) 5
Having each data value on a separate line in the file is rather
cumbersomethis is required by the separate execution of each
READ (1, *) X(I) in the DO loop. Fortran allows the use of an implied
DO to read or print all or part of an array. Simply replace the entire
DO construct in the program with

READ (1, *) ( X(I), I = 1, N )


Note that the syntax requires parentheses around the implied DO.
BASKOM-5 (YAKNI IDRIS) 6
Basic Rules and Notation
The array is our first example in Fortran 90 of a compound object, i.e. an object which
can have more than one value. Arrays can be fairly complicated creatures. Only the
basics are mentioned here; more advanced features will be introduced later.
The statement
REAL, DIMENSION(10) :: X
declares X to be an array (or list) with 10 real elements, denoted by X(1), X(2), ..., X(10).
The number of elements in an array is called its size (10 in this case). Each element of
an array is a scalar (single-valued).
Array elements are referenced by means of a subscript, indicated in parentheses after
the array name. The subscript must be an integer expressionits value must fall within
the range defined in the array declaration.
So X(I+1) is a valid reference for an element of X as declared above, as long as (I+1) is
in the range 110. A compiler error occurs if the subscript is out of range.
BASKOM-5 (YAKNI IDRIS) 7
Basic Rules and Notation
By default arrays have a lower bound of 1 (the lowest value a subscript can take).
However, you can have any lower bound you like:

REAL, DIMENSION(0:100) :: A
declares A to have 101 elements, from A(0) to A(100). The upper bound must be
specified; if the lower bound is missing it defaults to 1.
An array may have more than one dimension. The bounds of each dimension must be
specified:

REAL, DIMENSION(2,3) :: A
A is a two-dimensional array. The number of elements along a dimension is called the
extent in that dimension. A has an extent of 2 in the first dimension, and an extent of 3 in
the second dimension (and a size of 6). Fortran allows up to seven dimensions. The
number of dimensions of an array is its rank, and the sequence of extents is its shape.
The shape of A is (2, 3), or (2x3) in matrix notation. A scalar is regarded as having a rank
of zero. We will concentrate mainly on one-dimensional arrays in this chapterit is more
appropriate to discuss two-dimensional arrays in the context of matrices
BASKOM-5 (YAKNI IDRIS) 8
Reading an unknown amount of data
The implied DO together with the IOSTAT specifier in READ provides a neat way of
reading an unknown amount of data into an array, where only the maximum size of the
array is given:

INTEGER, PARAMETER :: MAX = 100
REAL, DIMENSION(MAX) :: X

OPEN (1, FILE = 'DATA')
READ( 1, *, IOSTAT = IO ) ( X(I), I = 1, MAX )

IF (IO < 0) THEN
N = I - 1
ELSE
N = MAX
END IF

PRINT*, ( X(I), I = 1, N )
END

The data may be arranged in any format in the input file. Note that I is one greater than
the number of values read: it is incremented in the implied DO before the end-of-fileend-
of-filecondition is detected. Note also that on normal exit from the implied DO its value
would be MAX+1.


BASKOM-5 (YAKNI IDRIS) 9
Write a program to find the student with the highest
mark in a class assumes that there is only one top
student. If there could be more than one name at the
top, you can use an array to make a list of the top
names.
BASKOM-5 (YAKNI IDRIS) 10
IMPLICIT NONE
INTEGER :: I ! student counter
INTEGER :: IO ! value of IOSTAT
INTEGER, PARAMETER :: MAX = 100 ! maximum class size
INTEGER :: NumTop = 1 ! must be at least 1
REAL :: Mark ! general mark
REAL :: TopMark = 0 ! can't be less than 0
CHARACTER*15 :: Name ! general name
CHARACTER*15, DIMENSION(MAX) :: TopName ! top student

OPEN( 1, FILE = 'MARKS' )

DO
READ( 1, * , IOSTAT = IO) Name, Mark
IF (IO < 0) EXIT
IF (Mark > TopMark) THEN ! new top mark here
TopMark = Mark ! reset the top mark
NumTop = 1 ! only one at the top now
TopName(1) = Name ! here she is
ELSE IF (Mark == TopMark) THEN ! tie for top mark here
NumTop = NumTop + 1 ! advance top counter
TopName(NumTop) = Name ! add his name to the list
END IF
END DO

DO I = 1, NumTop
PRINT*, TopName(I), TopMark
END DO
END
BASKOM-5 (YAKNI IDRIS) 11
To understand what the program does run through it by hand (make
a list of the variables, and enter their values) with the following data:

Botha 58
Essop 72
Jones 72
Murray 72
Rogers 90
Tutu 90

Then run it on the computer as a check. Note that at the end the
name Murray will still be in the array, in TopName(3), but his name
will not be printed because NumTop has been reset to 2.
You could try to rewrite this program with TopName as an
allocatable array to save memory space.
BASKOM-5 (YAKNI IDRIS) 12
Variabel berlarik (berindeks)
Pernyataan DIMENSION
Bentuk umum:

DIMENSION array1(dim1), array2(dim2)

Kegunaan: untuk mendefinisikan sautu nama yang
merupakan suatu larik serta sekaligus menentukan
jumlah dari elemen-elemennya.
array1, array2 adalah nama larik yang didefinisikan .
dim1, dim2 adalah dimensi yang menunjukkan jumlah
elemen larik
Pernyataan DIMENSION hanya dapat diletakkan
dibagian awal dari program.
BASKOM-5 (YAKNI IDRIS) 13
Tulislah sebuah program untuk membaca
sejumlah N data bilangan. Kemudian
program menghitung jumlah total bilangan
dan nilai rata-ratanya. Setelah itu, data
bilangan yang dibaca ditampilkan kembali
dan ditampilkan juga hasil perhitungan .
BASKOM-5 (YAKNI IDRIS) 14
PROGRAM DIMENSI1
DIMENSION X(10)
WRITE(*,*) ' JUMLAH DATA = '
READ(*,*) N
TOTAL = 0.0
DO I=1,N
WRITE(*,'(A,I2)') ' DATA ',I
READ(*,*) X(I)
TOTAL = TOTAL + X(I)
END DO
RATA2 = TOTAL/N
WRITE(*,*) ' MENAMPILKAN KEMBALI DATA '
DO I=1,N
WRITE(*,'(A,I2,A,F12.4)') ' DATA',I, ' = ',X(I)
END DO
WRITE(*,*) ' HASIL PERHITUNGAN '
WRITE(*,'(A20,F12.4)') ' JUMLAH = ',TOTAL
WRITE(*,'(A20,F12.4)') ' NILAI RATA-RATA = ',RATA2
END
BASKOM-5 (YAKNI IDRIS) 15
Tulislah program untuk membaca jumlah titik
serta koordinat x dan y masing-masing.
Kemudian program menghitung jarak antara
dua titik yang berurutan dengan rumus
Phytagoras. Setelah itu program menghitung
jarak total dari titik awal sampai titik ujung.
BASKOM-5 (YAKNI IDRIS) 16
PROGRAM DIMENSI2
PARAMETER (M=100)
REAL X(M),Y(M), JARAK(M-1)
WRITE(*,*) ' JUMLAH TITIK = '
READ(*,*) N
DO I=1,N
WRITE(*,'(A,I2,A,\)') ' X',I,' = '
READ(*,*) X(I)
WRITE(*,'(A,I2,A,\)') ' Y',I,' = '
READ(*,*) Y(I)
END DO
WRITE(*,*) ' MENAMPILKAN KEMBALI DATA '
DO I=1,N
WRITE(*,100) ' X',I, ' ; Y',I,' =',X(I),' ;',Y(I)
END DO
100 FORMAT(A,I2,A,I2,A,F7.2,A,F7.2)
WRITE(*,*) ' HASIL PERHITUNGAN '
TOTAL = 0.0
DO I=1,N-1
DX = X(I+1) - X(I)
DY = Y(I+1) - Y(I)
JARAK(I)= (DX**2 + DY**2)**0.5
TOTAL = TOTAL + JARAK(I)
WRITE(*,'(A,I2,A,F12.4)')'JARAK',I,' = ',JARAK(I)
END DO
WRITE(*,'(A,F12.4)') ' JARAK TOTAL = ',TOTAL
END
BASKOM-5 (YAKNI IDRIS) 17
Program untuk menghitung jumlah 2 buah matrik
PROGRAM JUMLAH MATRIK
DIMENSION A(10,10),B(10,10),C(10,10)
CHARACTER*72 FIN,FOUT,JUDUL1,JUDUL2,JUDUL3
C menanyakan nama file masukan dan file keluaran
WRITE(*,90) 'NAMA FILE MASUKAN = '
READ(*,'(A)') FIN
WRITE(*,90) 'NAMA FILE KELUARAN = '
READ(*,'(A)') FOUT
OPEN(1,FILE=FIN,STATUS='UNKNOWN')
OPEN(2,FILE=FOUT,STATUS='UNKNOWN')
90 FORMAT(1X,A,\)
c membaca baris pertama dan kedua dari file masukan
READ(1,'(A)') JUDUL1
WRITE(*,*) JUDUL1
READ(1,*) JB,JK
WRITE(*,95) ' BARIS =',JB,' KOLOM =',JK
95 FORMAT(A,I2,A,I2)
c membaca baris ketiga dst dari file masukan
c data ini adalah data matrik pertama ([A])
READ(1,'(A)') JUDUL2
WRITE(*,*) JUDUL2
DO I=1,JB
READ(1,*) (A(I,J),J=1,JK)
WRITE(*,100) (A(I,J),J=1,JK)
END DO
100 FORMAT(10(1X,F7.2))
BASKOM-5 (YAKNI IDRIS) 18
c membaca baris berikutnya dari file masukan
c data ini adalah data matrik kedua ([B])
READ(1,'(A)') JUDUL3
WRITE(*,*) JUDUL3
DO I=1,JB
READ(1,*) (B(I,J),J=1,JK)
WRITE(*,100) (A(I,J),J=1,JK)
END DO
c menjumlahkan matrik -> [C] = [A] + [B]
DO I=1,JB
DO J=1,JK
C(I,J) = A(I,J) + B(I,J)
END DO
END DO
c menampilkan matrik hasil penjumlahan ([C])
WRITE(*,*) ' Hasil penjumlahan matrik'
WRITE(2,*) ' Hasil penjumlahan matrik'
DO I=1,JB
WRITE(*,100) (C(I,J),J=1,JK)
WRITE(2,100) (C(I,J),J=1,JK)
END DO
END
BASKOM-5 (YAKNI IDRIS) 19
kj
JK1
1 k
ik ij
B * A C


Program untuk menghitung perkalian dua matrik dengan rumus


Dimana nilai: i=1 s/d JB1 JB1 =jumlah baris matrik 1
j=1 s/d JK2 JK1=jumlah kolom matrik 1
k=1 s/d JK1 JK2=jumlah kolom matrik 2
BASKOM-5 (YAKNI IDRIS) 20
PROGRAM PERKALIAN MATRIK
DIMENSION A(10,10),B(10,10),C(10,10)
CHARACTER*72 FIN,FOUT,JUDUL1,JUDUL2,JUDUL3,JUDUL4
C menanyakan nama file masukan dan file keluaran
WRITE(*,90) 'NAMA FILE MASUKAN = '
READ(*,'(A)') FIN
WRITE(*,90) 'NAMA FILE KELUARAN = '
READ(*,'(A)') FOUT
OPEN(1,FILE=FIN,STATUS='UNKNOWN')
OPEN(2,FILE=FOUT,STATUS='UNKNOWN')
90 FORMAT(1X,A,\)
c membaca baris pertama dan kedua dari file masukan
READ(1,'(A)') JUDUL1
WRITE(*,*) JUDUL1
READ(1,*) JB1,JK1
WRITE(*,95) ' BARIS =',JB1,' KOLOM =',JK1
95 FORMAT(A,I2,A,I2)
c membaca baris ketiga dst dari file masukan
c data ini adalah data matrik pertama ([A])
READ(1,'(A)') JUDUL2
WRITE(*,*) JUDUL2
DO I=1,JB1
READ(1,*) (A(I,J),J=1,JK1)
WRITE(*,100) (A(I,J),J=1,JK1)
END DO
100 FORMAT(10(1X,F7.2))
BASKOM-5 (YAKNI IDRIS) 21
c membaca baris berikutnya dari file masukan
c data ini adalah data matrik kedua ([B])
READ(1,'(A)') JUDUL3
WRITE(*,*) JUDUL3
READ(1,*) JK2
WRITE(*,95) ' BARIS =',JK1,' KOLOM =',JK2
READ(1,'(A)') JUDUL4
WRITE(*,*) JUDUL4
DO I=1,JK1
READ(1,*) (B(I,J),J=1,JK2)
WRITE(*,100) (B(I,J),J=1,JK2)
END DO
c mengalikankan matrik -> [C] = [A] * [B]
DO I=1,JB1
DO J=1,JK2
C(I,J) = 0.0
DO K=1,JK1
C(I,J)=C(I,J)+A(I,K)*B(K,J)
END DO
END DO
END DO
c menampilkan matrik hasil perkalian ([C])
WRITE(*,*) ' Hasil perkalian matrik'
WRITE(2,*) ' Hasil perkalian matrik'
DO I=1,JB1
WRITE(*,100) (C(I,J),J=1,JK2)
WRITE(2,100) (C(I,J),J=1,JK2)
END DO
END

S-ar putea să vă placă și