Why reshape gives me 'insufficient virtual memory' error?

I have an extremely simple code,

program main  
implicit none
integer, parameter :: i4=selected_int_kind(9)
integer, parameter :: i8=selected_int_kind(15)
integer, parameter :: r8=selected_real_kind(15,9)
integer(kind=i8) :: np 
np = 2
call test03(np)
stop
end
subroutine test03(n)
integer, parameter :: i4=selected_int_kind(9)
integer, parameter :: i8=selected_int_kind(15)
integer, parameter :: r8=selected_real_kind(15,9)
integer ( kind = i8 ), intent(in) :: n
real ( kind = r8 ) :: warray(n,4),normal(n,4)
warray = 1.0
write(6,*) 'reshape', reshape(warray,shape(warray))
return
end subroutine test03

I use Intel OneAPI + visual studio 2015/2017.
Problem is, when I run it, it just give me '‘insufficient virtual memory’ error below,

in ‘debug’ mode it also have this error.

Does anyone know why?

Thank you very much in advance!

However, if I enable the below options setting default integer and real as kind 8, it works fine again.

On the other hand, if the warray is allocatable, then it works fine too,

program main  
implicit none
integer, parameter :: i4=selected_int_kind(9)
integer, parameter :: i8=selected_int_kind(15)
integer, parameter :: r8=selected_real_kind(15,9)
integer(kind=i8) :: np 
np = 2
call test03(np)
stop
end
subroutine test03(n)
implicit none
integer, parameter :: i4=selected_int_kind(9)
integer, parameter :: i8=selected_int_kind(15)
integer, parameter :: r8=selected_real_kind(15,9)
integer ( kind = i8 ), intent(in) :: n
real ( kind = r8 ), allocatable :: warray(:,:)
allocate(warray(n,4))
warray = 1.0
write(6,*) 'reshape', reshape(warray,shape(warray))
deallocate(warray)
return
end subroutine test03 

I just do not understand clearly why allocatable array works fine, while define warray(n,2) just give me the error.

I replied on the Intel forum - I cannot reproduce the problem, so I am likely using a different version or a different set of compiler options.

1 Like

Thank you so much! I replied there with more details,

On WSL the program runs fine with the Intel Fortran (ifort version 2021.1) compiler and default compiler settings.

I did however make some simplifications:

program main  

  implicit none
  
  integer, parameter :: i8 = selected_int_kind(15)
  integer, parameter :: r8 = selected_real_kind(15,9)
  integer(kind=i8) :: np 
  
  np = 2
  call test03(np)

contains

  subroutine test03(n)
    integer(kind=i8), intent(in) :: n
    real(kind=r8) :: warray(n,4)
    warray = 1.0_r8
    write(*,*) 'reshape', reshape(warray,shape(warray))
  end subroutine test03

end program

When creating such minimal reproducer examples I suggest using a clear style. This makes it easier for readers to analyze your code. I also took the liberty of making the procedure internal and removing any declarations that have nothing to do with the problem at hand. (Another suggestion would be to drop using names like i8 and r8 since the suffix 8 provides no meaning and arguably only makes things more confusing).

I would also highly discourage changing the default real lengths (as seen from the settings shown at the Intel Community forum) for reasons explained before:

Thank you very much!

Could you please add

/heap-arrays0

in addition to /O3 /QxHost ?

In linux it may be
-heap-arrays

It seems heap array cause the problem, at least on windows 10 it is so.

If I do not set heap array then it does not have problem.

Please see my reply here.

community.intel.com/t5/Intel-Fortran-Compiler/Why-reshape-gives-me-insufficient-virtual-memory-error/m-p/1315188#M157538