Over the last couple of days, I’ve been playing with OpenMP (compiler = gfortran 12.2.0). While doing so on a rather simple piece of code, I realized that once a given array exceed a certain size, the program would fail at runtime.
Initially, I though the issue was caused by the $omp directives, but I finally realized that even if I removed all $omp directives, the problem persisted. Ultimately, I was able to pin down the problem to an unexpected (for me) clash between OpenMP and do concurrent
loops.
In my computer (windows with gcc), the simple program below runs well for “any” array size if compiled without the flag -fopenmp
. In contrast, with -fopenmp
it fails for N>=360 raising the following cryptic message:
<ERROR> Execution failed for object " filename.exe "
<ERROR>*cmd_run*:stopping due to failed executions
STOP 1
program test_do_concurrent_omp_bug
use, intrinsic :: iso_fortran_env, only: real64
implicit none
integer, parameter :: rk = real64
integer, parameter :: N = 370 ! raise me until it breaks!
real(rk) :: x(N**2)
print *, "Running..."
call foo(x)
print *, "Done!"
contains
subroutine foo(u)
real(rk), intent(out) :: u(:)
real(rk) :: a(0:N, N)
integer :: i, j
a = 0._rk
do concurrent(i=1:N, j=1:N)
u((j - 1)*N + i) = a(i, j)
end do
end subroutine foo
end program test_do_concurrent_omp_bug
Has anyone observed something similar? Is this a bug or a feature? If this is a general problem, it would appear that do concurrent
loops effectively preclude using OpenMP…