Array Arguments

Passing scalar arguments is straightforward, but many, perhaps most, Fortran programs are oriented around arrays and must pass them to and from subprograms. Since Fortran passes all variables by reference, i.e. by passing a pointer, there is no special behavior compared to scalars, unlike many other languages.

Passing Arrays to Subprograms

  • Arrays may be passed in one of three ways.
  • Static
    • Dimensions are declared as fixed numbers in both calling unit and callee.
  • Automatic
    • Dimensions may be passed in the argument list
  • Assumed-Shape
    • Only the rank is given, with an appropriate number of colons.
    • Assumed-shape arrays require an interface.

Examples We will show examples for subroutines but the rules are the same for functions. Static:

real, dimension(100) :: A

call sub(A)

subroutine sub(A)
real, dimension(100) :: A  ! in sub

A variable may be used but it must be declared PARAMETER. Some compilers, specifically Intel’s, may require that the parameter be declared before any arrays are declared that use it.

integer, parameter  :: N=100
real, dimension(N)  :: A
real, dimension(N,N):: B

Automatic:

real, dimension(100) :: A

call sub(A,n)
subroutine sub(A,n)
real, dimension(n) :: A  ! in sub

Assumed-shape:

integer,parameter  :: n=100
real, dimension(n) :: A

call sub(A)

subroutine sub(A)
real, dimension(:) :: A   ! in sub

Though the dimensions need not be known for assumed-shape arrays, the rank must match.

Example

program passit
implicit none

   integer, parameter   :: n=4
   integer, dimension(2):: sh
   real, dimension(4*n)   :: V
   real, dimension(n,n) :: A
   real, allocatable, dimension(:,:) :: B
   integer              :: i

   interface
      subroutine mysub1(X)
         implicit none
         real,dimension(:,:), intent(inout) :: X
      end subroutine
      subroutine mysub2(X,n)
         implicit none
         integer,             intent(in)    :: n
         real,dimension(n,n), intent(inout) :: X
      end subroutine
   end interface  

   V=[(real(i),i=1,16)]
   sh=[4,4]
   A=reshape(V,sh)

   allocate(B(n,n))
   B=A+2.

   call mysub1(A)
   call mysub2(A,n)
   call mysub1(B)
   call mysub2(B,n)

end program

subroutine mysub1(X)
   implicit none
   real,dimension(:,:), intent(inout) :: X
   
   print *, shape(X), X(2,2)
end subroutine

subroutine mysub2(X,n)
   implicit none
   integer,             intent(in)    :: n
   real,dimension(n,n), intent(inout) :: X
   
   print *, shape(X), n, X(2,2)
end subroutine

Allocating Arrays in a Subprogram

You may allocate an array inside a subprogram and return it. An interface is required. The array must be declared allocatable throughout the chain of calling units and must be intent(inout).

In the example below, no value is assigned initially. Most compilers will initialize the array to zero, but this is not guaranteed.

Exercise Run the program as is. Correct the lack of initialization in the subroutine.

program passit
implicit none

   integer, parameter   :: n=4
   integer, dimension(2):: sh
   real, dimension(4*n)   :: V
   real, dimension(n,n) :: A
   real, allocatable, dimension(:,:) :: B
   integer              :: i

   interface
      subroutine mysub1(X)
         implicit none
         real,dimension(:,:), allocatable, intent(inout) :: X
      end subroutine
      subroutine mysub2(X,n)
         implicit none
         integer,             intent(in)    :: n
         real,dimension(n,n), intent(inout) :: X
      end subroutine
   end interface  

   V=[(real(i),i=1,16)]
   sh=[4,4]
   A=reshape(V,sh)

!   allocate(B(n,n))
!   B=A+2.

   call mysub1(B)
   print *, B(1,1)
!   call mysub2(B,n)

end program

subroutine mysub1(X)
   implicit none
   real,dimension(:,:), allocatable, intent(inout) :: X
   integer m
   
   m=4
   allocate(X(4,4))
   X=5
   print *, shape(X), X(2,2)
end subroutine

subroutine mysub2(X,n)
   implicit none
   integer,             intent(in)    :: n
   real,dimension(n,n), intent(inout) :: X
   
   print *, shape(X), n, X(2,2)
end subroutine

Local Arrays in Subprograms

Arrays that are local (not in the parameter list) to a subprogram may be sized using an integer passed to the subprogram.

double precision function myfunc(A,n)
integer,                        intent(in) :: n
double precision, dimension(n), intent(in) :: A
double precision, dimension(n)             :: B

  do things with A and B
  myfunc=whatever
end function
Previous
Next