Subprogram Arguments

Pass by Reference and INTENT

Unlike most languages, Fortran passes all arguments by reference. This effectively means that what is actually passed is the memory location of the argument. Consequently, any change to the argument in the subprogram, intended or not, will change the variable outside as well. Changing the value of an argument is called a side effect. Side effects can be legitimate – subroutines rely on them – but they should be controlled. For this reason, Fortran introduced the INTENT attribute for subprogram parameters.

INTENT(IN)   ! Changing the variable in the subprogram throws a fatal error
INTENT(OUT)  ! Not changing the variable in the subprogram throws a fatal error
INTENT(INOUT)! Indicates that the programmer intends to overwrite the variable

Example

subroutine mysub(x,y,z)
   real, intent(in)    :: x
   real, intent(out)   :: y
   real, intent(inout) :: z
      y=x-z
      z=y+x
end subroutine

As a general rule, all arguments to a FUNCTION should be INTENT(IN).

Saving and Deallocating Subprogram Arguments

According to the standard, the memory used by local variables in a subprogram is freed upon exit from the procedure. Allocatable local arrays are automatically deallocated (this is a form of “garbage collection”). If you need some local variables to retain their value from one call to another, use the SAVE keyword

SAVE var1, var2, var3
SAVE

With no variable list it saves all local variables. Note that allocatable local arrays cannot be SAVEd.

Many compilers do not actually free the memory of non-allocatable local variables and some old programs rely on this behavior. Compilers have an option to ensure that all local variables are saved.

gfortran -fno-automatic mycode.f90
ifort -save mycode.f90

Optional and Keyword Arguments

Optional Arguments

Subroutines and functions may take optional arguments. Such arguments need not be passed. If they are passed, they take on the passed value. They are declared with the OPTIONAL attribute.

subroutine mysub(x,y,z,w)
implicit none
real, intent(in)           ::x,y
real, intent(in), optional ::z,w

The call to the previously-defined subroutine could be

callmysub(a,b)

in which case c and d would have no values and the subroutine would need to handle that situation appropriately. The call could also be

callmysub(a,b,c)

or

callmysub(a,b,c,d)

depending on how many of the optional arguments needed to be passed.

Keyword Arguments

Suppose it were desired to pass d but not c in the preceding subroutine. The c parameter can be skipped by using a keyword argument; the optional argument is called as

dummy=actual

where dummy is its name in the program unit where it is defined, and the actual argument is its name in the calling program unit.

Example

callmysub(aa,bb,w=d)

Positional (non-optional) arguments must appear before any optional or keyword arguments.

The PRESENT Intrinsic

The PRESENT() intrinsic function tests whether a particular optional argument is present in the argument list of the caller. If it is not present, defaults can be set or other action taken.

Example

IF (PRESENT(w)) THEN
   dd=w
ELSE
   dd=3.14
ENDIF

Passing Character Variables

Characters declared with a fixed length may be passed to a subprogram using a dummy length.

character(len=20) :: str
   call mysub(str)
end program
subroutine mysub(str)
   implicit none
   character(len=*), intent(in) :: str
end subroutine

Passing a Subprogram Name

The name of a subprogram can be passed to another subprogram. Example a numerical-integration subroutine needs to be able to call the function to be integrated.

subroutine trap(f,a,b,h,n)

where f is a function.

The procedure name to be passed must have an interface in the unit that invokes the subprogram that will take this parameter. The subprogram must also have an interface for the passed procedure. The older syntax EXTERNAL func may be used for the parameter, but new code should use INTERFACE. This will result in an INTERFACE block within another INTERFACE, which may look a bit wordy but is the modern way to declare this type of parameter.

interface
  real function trap(f,a,b,h,n)
      implicit none
      real,    intent(in)   :: a, b, h
      integer, intent(in)   :: n
      interface
         real function f(x)
         implicit none
         real, intent(in) :: x
         end function
       end interface
   end function
   real function f(x)
        implicit none
        real, intent(in) :: x
   end function
end interface
Full example of passing a subprogram as a dummy variable

program trapezoid
implicit none
                                                                                
! Calculate a definite integral using trapezoid rule
                                                                                
real    :: a, b
integer :: n

real    :: h, integral
real    :: x
integer :: i, nargs
character(len=16) lb, ub, ns

interface 
  real function trap(f,a,b,h,n)
      implicit none
      real,    intent(in)   :: a, b, h
      integer, intent(in)   :: n
      interface
         real function f(x)
         implicit none
         real, intent(in) :: x
         end function
       end interface
   end function
   real function f(x)
        implicit none
        real, intent(in) :: x
   end function
end interface

  nargs=command_argument_count()
  if ( nargs .ne. 3 ) then
     stop "Usage: arguments are lower bound, upper bound, number of steps"
  else
     call get_command_argument(1,lb)
     read(lb,'(f16.9)') a
     call get_command_argument(2,ub)
     read(ub,'(f16.9)') b
     call get_command_argument(3,ns)
     read(ns,'(i10)') n
  endif

   h=(b-a)/n
   integral=trap(f,a,b,h,n)
                                                                                
   integral = (f(a) + f(b))/2.0
   x=a
   do i=1, n-1
      x = x+h
      integral = integral + f(x)
   enddo
                                                                                
   integral = h*integral
   print *, integral

end program

real function trap(f, a, b, h, n)
   implicit none
   real,    intent(in)   :: a, b, h
   integer, intent(in)   :: n

   interface
     real function f(x)
        implicit none
        real, intent(in) :: x
     end function
   end interface

   real   :: x
   integer:: i
   real   :: integral

   integral = (f(a) + f(b))/2.0

   x=a
   do i=1, n-1
      x = x+h
      integral = integral + f(x)
   enddo

   trap   = integral*h
   return

end function
                                                                                
real function f(x)
  implicit none
  real, intent(in):: x
     f=sin(x)
end function


Exercise

Write a program for comparing Euclidean distances. The program should implement a function that takes the coordinates of two points and returns their distance. Implement a subroutine that invokes this function for three points to determine which of the first two is closer. Use interfaces. Each calling unit must have an interface for every subprogram it calls.

Use intent and implicit none. Remember that implicit none must be declared in each unit. You may use arrays to represent the points.

Example Solution

program euclid
implicit none

   real, dimension(2)       :: p1, p2, p3
   integer                  :: winner

   interface
      subroutine compare_points(p1,p2,p3,winner)
      implicit none
         real, dimension(2), intent(in)  :: p1, p2, p3
         integer,            intent(out) :: winner
      end subroutine
   end interface

   !Point 1
   write(*,'(a)',advance='no') "Please enter the first point, two reals separated by a comma: "
   read(*,*) p1(1), p1(2)

   !Point 2
   write(*,'(a)',advance='no') "Please enter the second point, two reals separated by a comma: "
   read(*,*) p2(1), p2(2)

   !Point 3
   write(*,'(a)',advance='no') "Please enter the third point, two reals separated by a comma: "
   read(*,*) p3(1), p3(2)

   call compare_points(p1,p2,p3,winner)

   if (winner==1) then
      print *, "Point 1 is closer to Point 3"
   else if (winner==2) then
      print *, "Point 2 is closer to Point 3"
   else if (winner==0) then
      print *, "The distance is the same"
   else
      print *, "Error"
   endif

end program

real function euclidean(p1,p2)
   implicit none
   real, dimension(2), intent(in) :: p1, p2

   euclidean=sqrt((p2(1)-p1(1))**2+(p2(2)-p2(1)))
end function

subroutine compare_points(p1,p2,p3,winner)
   implicit none
   real, dimension(2), intent(in)  :: p1, p2, p3
   integer,            intent(out) :: winner
   real                            :: dist13, dist23
   interface
      real function euclidean(p1,p2)
         implicit none
         real, dimension(2), intent(in) :: p1, p2
      end function
   end interface

   winner=-1

   dist13=euclidean(p1,p3)
   dist23=euclidean(p2,p3)

   if (dist13==dist23) winner=0
   if (dist13<dist23)  winner=1
   if (dist13>dist23)  winner=2

end subroutine
   


Previous
Next