A few short examples that illustrate the use of arrays in computation are presented here.
In the above code, the DO variable i runs from -100 to 100. For each value of i, array elements a(i) is set to zero.INTEGER, PARAMETER :: LOWER = -100, UPPER = 100 INTEGER, DIMENSION(LOWER:UPPER) :: a INTEGER :: i DO i = LOWER, UPPER a(i) = 0 END DO
This code sets array element Array(i) to i. Thus, Array(1) contains 1, Array(2) contains 2, etc.INTEGER, PARAMETER :: BOUND = 20 INTEGER, DIMENSION(1:BOUND) :: Array INTEGER :: i DO i = 1, BOUND Array(i) = i END DO
As variable Element runs from 1 to ARRAY_SIZE, the remainder of dividing Element by 2 is used to set odd and even elements.INTEGER, PARAMETER :: ARRAY_SIZE = 50 INTEGER, DIMENSION(1:ARRAY_SIZE) :: OddEven INTEGER :: Element DO Element = 1, ARRAY_SIZE OddEven(Element) = MOD(Element, 2) END DO
For each value of k in the range of m and n, the value of DataArray(k) is added to an accumulator Sum.REAL, PARAMETER :: MAX_SIZE = 100 REAL, DIMENSION(-MAX_SIZE:MAX_SIZE) :: DataArray REAL :: Sum INTEGER :: m, n, k READ(*,*) m, n Sum = 0.0 DO k = m, n Sum = Sum + DataArray(k) END DO
REAL, PARAMETER :: LENGTH = 35 REAL, DIMENSION(1:LENGTH) :: A, B, C INTEGER :: Index DO Index = 1, LENGTH C(Index) = A(Index) + B(Index) END DO
REAL, PARAMETER :: LENGTH = 35
REAL, DIMENSION(1:LENGTH) :: A, B, C
INTEGER :: Index
DO Index = 1, LENGTH
IF (A(Index) > B(Index) THEN
C(Index) = A(Index)
ELSE
C(Index) = B(Index)
END IF
END DO
In the above, Elements_Used is read in and indicates that only the first Elements_Used elements will be used for inner product computation.REAL, PARAMETER :: VECTOR_SIZE = 10 REAL, DIMENSION(1:VECTOR_SIZE) :: Vector1, Vector2 REAL :: InnerProduct INTEGER :: Elements_Used, n READ(*,*) Elements_Used InnerProduct = 0.0 DO n = 1, Elements_Used InnerProduct = InnerProduct + Vector1(n)*Vector2(n) END DO
INTEGER, PARAMETER :: BEGIN = -100, END = 50
INTEGER, DIMENSION(BEGIN:END) :: Data
INTEGER :: Minimum, Location
INTEGER :: k
Minimum = Data(BEGIN)
Location = BEGIN
DO k = BEGIN+1, END
IF (Data(k) < Minimum) THEN
Minimum = Data(k)
Location = k
END IF
END DO
WRITE(*,*) "The minimum is in position ", Location
WRITE(*,*) "Minimum value is ", Minimum
In the above, Minimum is used to hold the
minimum-up-to-now and Location is used to record the
position of the minimum. At the beginning, there is only one
element and it is assumed to be the minimum. Therefore,
Minimum is Data(BEGIN) and Location is the
first location BEGIN.
Then, the process starts with the next element (i.e., BEGIN+1). For each element encountered, Data(k), if its value is less than Minimum, then Minimum is no more a minimum and should be changed. The change consists of replacing the minimum-up-to-now with the value of Data(k) and memorizing the location. Therefore, after all elements are processed, Minimum holds the minimum of the array and Location is the location of the minimum.
INTEGER, PARAMETER :: BEGIN = -100, END = 50
INTEGER, DIMENSION(BEGIN:END) :: Data
INTEGER :: Left, Right
INTEGER :: Minimum, Location
INTEGER :: k
READ(*,*) Left, Right
Minimum = Data(Left) ! **** changed ****
Location = Left
DO k = Left+1, Right
IF (Data(k) < Minimum) THEN
Minimum = Data(k)
Location = k
END IF
END DO
WRITE(*,*) "The minimum between ", Left, " and " &
Right, " is in position ", Location
WRITE(*,*) "Minimum value is ", Minimum
In the above, Left and Right are read in. Then, the
code would find the minimum and its location of array elements
Data(Left), Data(Left+1), Data(Left+2),
...., Data(Right-1) and Data(Right).
INTEGER, PARAMETER :: NO_OF_PROBLEMS = 20
INTEGER, DIMENSION(1:NO_OF_PROBLEMS) :: Solution, Answer
INTEGER :: i, Count, IO
READ(*,*) (Solution(i), i=1, NO_OF_PROBLEMS)
DO
READ(*,*,IOSTAT=IO) (Answer(i), i=1, NO_OF_PROBLEMS)
IF (IO < 0) EXIT
Count = 0
DO i = 1, NO_OF_PROBLEMS
IF (Solution(i) == Answer(i)) THEN
Count = Count + 1
END IF
END DO
WRITE(*,*) (Answer(i), i=1, NO_OF_PROBLEMS), &
REAL(Count)/NO_OF_PROBLEMS * 100.0
END DO
Array Solution() stores the solution, while array
Answer() stores a student's answer. The above code
counts the number of correct answers and displays the answer
and a percentage.
The outer DO iterates until no student answer is in the input (i.e. IO < 0). For each student, his/her answer is read into array Answer(). The inner DO counts how many answers are correct. Then, the answers and a percentage are displayed.