Is there any practically significant difference between automatic arrays saved on the heap and allocatable arrays?
As an example, consider the following code (edit: I added functions with array results inspired by the comment of @RonShepard).
module s_mod
implicit none
private
public :: sf_auto, sf_alloc, af_auto, af_alloc
contains
function sf_auto(n) result(s)
integer, intent(in) :: n
real :: s
real :: x_auto(n)
x_auto = 1.0
s = sum(x_auto)
end function sf_auto
function sf_alloc(n) result(s)
integer, intent(in) :: n
real :: s
real, allocatable :: x_alloc(:)
allocate (x_alloc(n))
x_alloc = 1.0
s = sum(x_alloc)
deallocate (x_alloc)
end function sf_alloc
function af_auto(n) result(a_auto)
integer, intent(in) :: n
real :: a_auto(n)
a_auto = 1.0
end function af_auto
function af_alloc(n) result(a_alloc)
integer, intent(in) :: n
real, allocatable :: a_alloc(:)
allocate (a_alloc(n))
a_alloc = 1.0
end function af_alloc
end module s_mod
program test
use :: s_mod, only:sf_auto, sf_alloc, af_auto, af_alloc
implicit none
integer :: i
integer, parameter :: n = 20
do i = 1, n
write (*, *) 2**i, sf_auto(2**i)
end do
do i = 1, n
write (*, *) 2**i, sf_alloc(2**i)
end do
do i = 1, n
write (*, *) 2**i, sum(af_auto(2**i))
end do
do i = 1, n
write (*, *) 2**i, sum(af_alloc(2**i))
end do
end program test
Name this piece of code as test.f90
. Compile it with
gfortran test.f90
or
ifort -heap-arrays test.f90
In both cases, x_auto
and a_auto
will be saved on the heap. Then, is there any practically significant difference between sf_auto
and sf_alloc
? Is there any scenario in which they will behave noticeably differently? Are they actually “equivalent” on the assembly level with only minor differences? What if the code is compiled using other compilers while ensuring that sf_auto
is saved on the heap?
This question is asked mostly out of curiosity, but I hope it is not totally irrelevant, recalling that @awvwgk mentioned in a previous thread that the implementation of stdlib
uses automatic arrays where possible.
Thanks.