Why /heap-arrays0 cause /qopenmp show access violation for do concurrent?

Dear all,

A very simple question about do concurrent. Code is below,

program mainomp
  implicit none
  integer, parameter :: r8=selected_real_kind(15,9)
  real, allocatable :: x(:,:,:),ks(:,:,:),xs(:,:,:)
  integer :: i,j,nstep,np,nd,l,k
  real(kind=r8), parameter :: as(4,4) = reshape([ &
    &  0.0_r8,              0.0_r8,              0.0_r8,              0.0_r8, &
    &  2.71644396264860_r8, 0.0_r8,              0.0_r8,              0.0_r8, &
    & -6.95653259006152_r8, 0.78313689457981_r8, 0.0_r8,              0.0_r8, &
    &  0.0_r8,              0.48257353309214_r8, 0.26171080165848_r8, 0.0_r8 ], [4,4]) 
  np=10**5
  nd=2
  nstep=10**3
  allocate(x(np,nd,0:nstep))
  allocate(xs(np,nd,4))
  allocate(ks(np,nd,4))
  do k = 1, nstep
    do j = 1,4
      do concurrent (l=1:nd)
        xs(:,l,j) = x(:,l,k-1) + matmul(ks(:,l,:j-1),as(:j-1,j))           
      enddo  
    enddo   
  enddo
end program mainomp

According to Intel documentation, when -qopenmp is enabled, it should automatically parallelize the do concurrent, which is great.

However when I enable -qopenmp and I also enable heap-arrays0 as below,

it just give me access violation error

forrtl: severe (157): Program Exception - access violation
Image              PC                Routine            Line        Source
openMPtest.exe     00007FF6CC756A0A  Unknown               Unknown  Unknown
openMPtest.exe     00007FF6CC7317B2  MAIN__                     20  main_omp.f90
libiomp5md.dll     00007FF80756D853  Unknown               Unknown  Unknown
libiomp5md.dll     00007FF8074CEC67  Unknown               Unknown  Unknown
libiomp5md.dll     00007FF8074D0A26  Unknown               Unknown  Unknown
libiomp5md.dll     00007FF807487751  Unknown               Unknown  Unknown
openMPtest.exe     00007FF6CC73155C  MAIN__                     19  main_omp.f90
openMPtest.exe     00007FF6CC761E5E  Unknown               Unknown  Unknown
openMPtest.exe     00007FF6CC76223C  Unknown               Unknown  Unknown
KERNEL32.DLL       00007FF8A9EC7034  Unknown               Unknown  Unknown
ntdll.dll          00007FF8AABA2651  Unknown               Unknown  Unknown

at line

xs(:,l,j) = x(:,l,k-1) + matmul(ks(:,l,:j-1),as(:j-1,j))         

However, without heap-arrays as below, the code with -qopenmp works, no error.

Just wonder, does anyone have similar issues?
Why heap-arrays will cause access violation? How to solve this problem?

Thanks much in advance!

PS.

Intel’s document webpage below,

Visual Studio /qopenmp settings can also be set from below menu,

Heave you tried telling Intel?

What does this option do ?

If it sets the heap array size limit to zero, which could imply moving all ALLOCATE arrays to the stack, then you should calculate the array sizes and ensure that they can fit in the stack size allocated.

Note that if you need to enlarge the stack size, for allocated arrays plus possibly the array sections “ks(:,l,:j-1)” and “as(:j-1,j)” you will need to check how this is applied to concurrent arrays.

( OpenMP stack size modifications for other than the primary thread depends on the compller implementation, so you should check this carefully for -qopenmp
OpenMP can also duplicate PRIVATE arrays in the primary stack, although there is no indication of this occurring in your post )

1 Like

@JohnCampbell Thank you very much!
/heap-arrays0 on Windows is the same as -heap-arrays on Linux for Intel Fortran. It means put any array larger than 0 bytes on heap. The explanation can be see from the bottom of the screenshot below,


By default is blank. If I set to 0 then it means put everything on heap. You can set it to any value.

I realize that perhaps for -qopenmp, instead of setting heap-arrays, I should increase stack size. So I leave the heap arrays as blank, and I increased the stack size as below to the biggest value possible (the biggest value for integer*4),

Then the code also works, no error.

1 Like

I’ve tried a few variations on the above code. It’s definitely a bug with IFORT’s DO CONCURRENT implementation and it’s interaction with heap-arrays. So sure, for now just avoid using heap-arrays with DO CONCURRENT and I’ll get a bug report opened on this. This is the first someone has tested the combination of DO CONCURRENT, -openmp, and -heap-arrays.

2 Likes

Interesting that your program is working with stack = 2^31 bytes (2 GBytes)
For Windows x64, I am told there is a size limit for code + stack, although I am not sure of the limit (2GBytes or 4 GBytes?) I usually set the stack to 0.5 GBytes and for arrays requiring larger than this, I would place them on the heap.
The stack is best utilised by small arrays, although the Windows stack has some poor design features.

1 Like