I developed a MWE to test possible stack-overflow runtime errors (in Windows) when using the array functions reshape
, sum
, any
, where
. My example has three files: mymod1.f90, mymod2.f90 and test_reshape.f90 (attached at the end of this post)
mymod1 is compiled with the flag /heap-arrays0
so that it always runs
mymod2 instead is compiled without /heap-arrays0
to test if a stack overflow occurs
mymod1 and mymod2 are identical and test the following Fortran functions:
reshape
, sum
, any
, where
Note that ALL arrays are declared as allocatable
Nonetheless, there is a stack overflow when calling test2 in mymod2. The stack overflow occurs when the where
statement is reached, not with the others. I found this behavior quite strange. Does this mean that where
creates some temporary arrays on the stack, while reshape
,sum
,any
do not?
What seems to transpire from this test is that
-
Declaring ALL arrays as allocatable is not enough to avoid problems with the stack (at least in Windows). You need to compile with
/heap-arrays0
to be on the safe side. -
But
reshape
,sum
,any
are ok even without/heap-arrays0
, whilewhere
gives the run time error
I was trying to avoid compiling with /heap-arrays0
because in some of my codes (not shown here) there is a big performance penalty, but it seems than in that case it becomes risky to use some Fortran array functions like where
which are however quite useful
Any comment greatly appreciated, thanks!
Here is the main program:
! Compilation
! ifort /heap-arrays0 -c mymod1.f90
! ifort -c mymod2.f90
! ifort -c test_reshape.f90
! ifort mymod1.obj mymod2.obj test_reshape.obj -o win_run.exe
! Run program
! .\win_run.exe
program test_reshape
use mymod1, only: test1
use mymod2, only: test2
implicit none
integer :: n,m
n = 10000
m = 2000
write(*,*) "-----------------------"
write(*,*) "Calling sub test1.."
call test1(n,m)
write(*,*) "-----------------------"
write(*,*) "Calling sub test2.."
call test2(n,m)
end program test_reshape
and here are the two modules:
module mymod1
! ifort /heap-arrays0 -c mymod1.f90
implicit none
contains
subroutine test1(n,m)
implicit none
integer, intent(in) :: n, m
real(8), allocatable :: x(:,:), xvec(:)
real(8) :: sum_x
allocate(x(n,m))
call RANDOM_NUMBER(x)
xvec = reshape(x,[n*m])
write(*,*) "reshape is ok"
sum_x = sum(x)
write(*,*) "sum is ok"
if (any(x>0.1d0)) then
write(*,*) "Some elements of x are larger than 0.1"
endif
write(*,*) "any is ok"
where (xvec<0.5d0)
xvec = 0d0
elsewhere
xvec = 1d0
end where
write(*,*) "where is ok"
write(*,*) "Shape of x = ", shape(x)
write(*,*) "Shape of xvec = ", shape(xvec)
end subroutine test1
end module mymod1
module mymod2
! ifort -c mymod2.f90
implicit none
contains
subroutine test2(n,m)
implicit none
integer, intent(in) :: n, m
real(8), allocatable :: x(:,:), xvec(:)
real(8) :: sum_x
allocate(x(n,m))
call RANDOM_NUMBER(x)
xvec = reshape(x,[n*m])
write(*,*) "reshape is ok"
sum_x = sum(x)
write(*,*) "sum is ok"
if (any(x>0.1d0)) then
write(*,*) "Some elements of x are larger than 0.1"
endif
write(*,*) "any is ok"
where (xvec<0.5d0)
xvec = 0d0
elsewhere
xvec = 1d0
end where
write(*,*) "where is ok"
write(*,*) "Shape of x = ", shape(x)
write(*,*) "Shape of xvec = ", shape(xvec)
end subroutine test2
end module mymod2
mymod1.f90 (669 Bytes)
mymod2.f90 (669 Bytes)
test_reshape.f90 (1.6 KB)