Hi all,
I’m wondering if anyone has any insights as to why openMP parallel blocks tend to behave poorly with allocatable character variables. In this MWE, just the existence of an allocatable character variable (that is allocated at runtime) results in a runtime error (I’m using gfortran 14.2 on Windows, compiling only with the -fopenmp flag) when the code enters the openMP block:
program scratch
use omp_lib, only: omp_set_num_threads
use iso_fortran_env, only: output_unit
integer :: n = 1
character(len=:), allocatable :: char1
character(len=:), allocatable :: char2
integer :: x = 5
call omp_set_num_threads(n)
char1 = 'teststring1234'
char2 = 'teststring1234'
print *, char2
!$OMP parallel
! If I uncomment the following two lines, the error is avoided
! char1 = char1
! char2 = char2
call do_anything(char1, x)
call do_anything(char2, x)
print *, x
!$OMP end parallel
contains
subroutine do_anything(char,y)
character(len=*), intent(in) :: char
integer, intent(inout) :: y
y = 2 * y
end subroutine do_anything
end program
The resulting error is:
In file 'scratch.f90', around line 14: Error allocating 2879386768 bytes: Not enough space
Obviously this program doesn’t do anything, and it doesn’t make sense to have a function which doesn’t use one of its arguments, but the point is that the purpose of the function is irrelevant. Interestingly, first assigning the variables to themselves within the omp block prevents the error.
Also, the reason I write the MWE with two different allocatable variables is that, at least on my machine, using just one of them doesn’t lead to the runtime error. Although if I were to just use e.g., char1, and then within the omp block I try to assign it to another (non allocatable) character variable, it just assigns gibberish. So I assume there’s still some memory problems happening when I just use 1 variable, and its allocating a huge amount, it’s just not enough to cause the runtime error.
In my real code, I can pretty easily avoid this error, but I’m still wondering if anyone knows why this happens in the first place?