Welcome to AE Resources
Converted document Converted document

FORTRAN 90+: DISTRIBUTED MEMORY USING ALLOCATABLE ARRAYS

The memory required for a complex program can grow so that it is difficult to operate in an efficient manner. One way to manage memory so that it is minimized is through allocatable arrays.
Allocatable arrays are referred to as deferred-shape arrays. The effect is that the size of the array is not set a priori, but can be changed through out the program and discarded at will. The declaration and a basic use of an allocatable array as part of the main program is
INTEGER, DIMENSION(:), ALLOCATABLE :: line
     REAL, DIMENSION(:,:), ALLOCATABLE :: paper
     INTEGER :: ierr, ierr2
     ALLOCATE(line(1:10), STAT=ierr)
     IF (ierr .NE. 0) THEN
          WRITE(*,*) "line: allocation request denied"
     END IF
     ALLOCATE(paper(1:10,1:50), STAT=ierr2)
     IF (ierr2 .NE. 0) THEN
          WRITE(*,*) "paper: allocation request denied"
     END IF
The reason for the IF statement and the STAT=ierr is to tell the user whether or not the allocation was successful. Because the space ALLOCATABLE used in memory is much more limited there is a chance that the operation will not be possible when it is carried out. STAT returns a value that is nonzero if the allocation request fails.
One of the advantages of using ALLOCATABLE arrays is the ability to delete arrays and thus free up space when they are no longer needed. This is done with DEALLOCATE. Before deallocating an array it is important to make sure it exists first as a compiler error will result if a call to deallocate an array that does not exist is used. The deallocation of the line array created above is shown below.
IF (ALLOCATED(line)) THEN
     DEALLOCATE(line, STAT=ierr)
END IF
Again STAT interrogates the status of the DEALLOCATE.
The array can be saved (for example, for the next time a subroutine is called) using the SAVE command.
Even without the use of the ALLOCATE and DEALLOCATE commands, the concept of adjustable arrays can be especially powerful with subroutines or functions if the array dimensions are passed to the subprogram. As an example, consider
PROGRAM aarray
INTEGER, PARAMETER :: length = 10
INTEGER :: i
REAL :: a(length)
​
DO i=1,10
  a(i) = 2.*i
ENDDO
​
WRITE(*,*) ’MAIN PROGRAM’
WRITE(*,*) a
​
CALL test(5, a(3:7))
​
CONTAINS
​
    SUBROUTINE test(n,b)
    INTEGER  :: n
    REAL, DIMENSION(n) :: b
​
    WRITE(*,*) ’IN SUBROUTINE’
    WRITE(*,*) b
​
    END SUBROUTINE test
​
END PROGRAM aarray
 
Only a subset of the vector, a, is being passed to the subroutine, and the code when executed yields the result:
MAIN PROGRAM
   2.0000000   4.0000000   6.0000000   8.0000000  10.0000000  
   12.0000000  14.0000000  16.0000000  18.0000000  20.0000000
IN SUBROUTINE
   6.0000000   8.0000000  10.0000000  12.0000000  14.0000000
A way to pass the entire array without having to dimension it twice is available in Fortran 90. Unlike prior versions of Fortran, Fortran 90 remembers the shape of an array. Therefore one correct way to pass the entire array, a, from the example above is
Next Page →
Next Page →