Skip to content

Instantly share code, notes, and snippets.

@certik
Created March 25, 2014 04:06
Show Gist options
  • Star 0 You must be signed in to star a gist
  • Fork 0 You must be signed in to fork a gist
  • Save certik/9755084 to your computer and use it in GitHub Desktop.
Save certik/9755084 to your computer and use it in GitHub Desktop.
program test
implicit none
integer, parameter :: dp = kind(0d0)
real(dp), allocatable :: x(:)
integer :: i, n
n = 10
allocate(x(n))
forall(i=1:n) x(i) = i
print *, foo(x)
contains
real(dp) function foo(a) result(r)
real(dp), intent(in) :: a(:)
r = sum(a)
end function
end program
@jeffhammond
Copy link

Hmm, I cannot remember what we could not do. Maybe it was just gfortran not supporting enough features.

The following was my failed attempt to recreate the issue from 2011.

==> fortran1.f90 <==
program test
implicit none
real, allocatable :: x(:)
integer :: i, n
real :: r
n = 10
allocate(x(n))
forall(i=1:n) x(i) = i
call foo(n,x,r)
print*,r
end program

==> fortran2.f90 <==
subroutine foo(n,a,r)
integer, intent(in) :: n
real, allocatable, intent(inout) :: a(:)
real, intent(out) :: r
if (.not. allocated(a)) allocate(a(n))
r = sum(a)
end subroutine

@certik
Copy link
Author

certik commented Mar 25, 2014

You can add these two into one file a.f90 like this:

subroutine foo(n,a,r)
integer, intent(in) :: n
real, allocatable, intent(inout) :: a(:)
real, intent(out) :: r
if (.not. allocated(a)) allocate(a(n))
r = sum(a)
end subroutine

program test
implicit none
real, allocatable :: x(:)
integer :: i, n
real :: r
n = 10
allocate(x(n))
forall(i=1:n) x(i) = i
call foo(n,x,r)
print*,r
end program

And compile with the common debug options for gfortran:

$ gfortran -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g -fcheck=all -fbacktrace a.f90
a.f90:17.8:

call foo(n,x,r)
        1
Error: Dummy argument 'a' of procedure 'foo' at (1) has an attribute that requires an explicit interface for this procedure
Fatal Error: Error count reached limit of 1.

The problem is that since the foo subroutine is not imported from some module (nor any interface for foo is provided), the Fortran compiler can't check types, so it fails. This is easy to fix (you can split the module and the main program into separate files, as should be done for a bigger project, but for these tests it's simpler to just keep things in one file):

module foolib
implicit none
private
public foo

contains

subroutine foo(n,a,r)
integer, intent(in) :: n
real, allocatable, intent(inout) :: a(:)
real, intent(out) :: r
if (.not. allocated(a)) allocate(a(n))
r = sum(a)
end subroutine

end module

!-----------------------------------------------

program test
use foolib, only: foo
implicit none
real, allocatable :: x(:)
integer :: i, n
real :: r
n = 10
allocate(x(n))
forall(i=1:n) x(i) = i
call foo(n,x,r)
print*,r
end program

Then it works as expected:

$ gfortran -Wall -Wextra -Wimplicit-interface -fPIC -fmax-errors=1 -g -fcheck=all -fbacktrace a.f90
$ ./a.out 
   55.000000    

Note that I've never used real, allocatable, intent(in) or real, allocatable, intent(inout). Usually, if I want to modify an array in place, I just use real, intent(inout). If I want to allocate array in the subroutine, I use real, allocatable, intent(out), then this array will be deallocated (if it was allocated) when the caller calls this subroutine, and the subroutine may or may not allocate it. An example is my implementation of loadtxt that behaves like NumPy's loadtxt, i.e. returns a 2D array with as many columns/rows as there are in the file.

Note also that Fortran automatically deallocates all allocated allocatable arrays when they run out of scope, so no leak is possible. You can use pointers if you want more control, those can leak. I almost never use pointers, just allocatable.

Sign up for free to join this conversation on GitHub. Already have an account? Sign in to comment