|
F90 provides much better support for dynamic arrays than C/C++
Defining a ONE-dimensional dynamic array:
REAL, DIMENSION( : ), ALLOCATABLE :: A ^^^^^^^^^^^ |
Allocating space for a ONE-dimensional dynamic array:
ALLOCATE(A(10)) !! A(1..10) ALLOCATE(A(-5:20)) !! A(-5..20) ALLOCATE(A(N)) !! A(1..N) |
Deallocating space of a dynamic array:
DEALLOCATE(A) |
Defining a TWO-dimensional dynamic array:
REAL, DIMENSION( : , : ), ALLOCATABLE :: A |
Allocating space for a TWO-dimensional dynamic array:
ALLOCATE(A(5, 10)) !! A(1..5, 1..10) ALLOCATE(A(1:3, -5:20)) !! A(1..3, -5..20) ALLOCATE(A(M, N)) !! A(1..M, 1..N) |
Deallocating space of a dynamic array:
DEALLOCATE(A) |
INTEGER :: errCode ALLOCATE( A(size), STAT = errCode) |
ALLOCATED( Allocatable-Variable ) |
The ALLOCATED intrinsic function will return TRUE if and it returns FALSE otherwise.
REAL, DIMENSION( : ), ALLOCATABLE :: A ... IF ( ALLOCATED (A) ) THEN print *, "A has been allocated" ELSE print *, "A has not been allocated" END IF |
REAL, TARGET :: r REAL, POINTER :: ptr ptr => r ! Make ptr points to r ptr = 1234 ! Same as "r = 1234" |
Notice that a pointer variables has a type
Type, DIMENSION( ... ), POINTER :: varName; |
Example: defining a pointer variable to a 2-dim array:
REAL, TARGET, DIMENSION(3,3) :: A REAL, DIMENSION(:,:), POINTER :: B B => A ! Make B points to A B(1,1) = 1234 ! Same as "A(1,1) = 1234" |
(for an explanation of what a COMMON block is: click here )
|
(for an explanation on how to define global variable using modules: click here )
Example: defining a global dynamic matrix in a module
MODULE myModule REAL, DIMENSION(:, :), ALLOCATABLE :: myMatrix END MODULE |
However...
|
Example: returning a dynamically allocated array
FUNCTION pivot_row( A ) real, dimension(:, :) :: A real, dimension( : ), pointer :: pivot_row -----------+ | integer, dimension ( 2 ) :: location | real, dimension(:), ALLOCATABLE, TARGET :: R <---------+ location = MAXLOC( A ) !! Find row + column !! index of MAX elem. R = ALLOCATE( SIZE(A(1, :) ) !! Allocate array R = A( location(1), : ) !! Copy pivot row pivot_row => R !! Return pointer to !! the dyn array END FUNCTION |
How to use a function that returns a pointer:
PROGRAM Main INTERFACE FUNCTION pivot_row( A ) real, dimension(:, :), target :: A real, dimension( : ), pointer :: pivot_row END FUNCTION END INTERFACE real, dimension(3, 3) :: A real, dimension(:), pointer :: p ! 1 pointer; ! points to an array p => pivot_row(A) END PROGRAM |
Example Program:
(Demo above code)
                       
NOTE:
|
Returning a pointer to a slice of the input array:
FUNCTION pivot_row( A ) real, dimension(:, :), target :: A real, dimension( : ), pointer :: pivot_row integer, dimension ( 2 ) :: location location = MAXLOC( A ) !! Find row + column index of MAX elem. pivot_row => A( location(1), : ) !! **** The pointer points to a row of the input array END FUNCTION |
This is not a copy
Updates to the returned row will change the original matrix
Example Program:
(Demo above code)