OpenMP error with allocatable character variables

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?

2 Likes

Hi,

I have some issues with allocatable character string with openmp and gfortran.
See this post :

As far as I know, this problem is not solved.

~Not sure how the resulting error comes about in your MWE; there’s no write or open file anywhere.~
Edit: The error of course refers to the source code, my bad.

In any case, compiling the MWE with -Wall gives a hint:

$ mpif90 -o test -Wall -fopenmp scratch.f90 
scratch.f90:24:31:

   24 |     subroutine do_anything(char,y)
      |                               1
Warning: Unused dummy argument 'char' at (1) [-Wunused-dummy-argument]
scratch.f90:13:18:

   13 |     !$OMP parallel
      |                  ^
Warning: '.char1' may be used uninitialized [-Wmaybe-uninitialized]
scratch.f90:28:30:

   28 |     end subroutine do_anything
      |                              ^
note: '.char1' was declared here
scratch.f90:13:18:

   13 |     !$OMP parallel
      |                  ^
Warning: '.char2' may be used uninitialized [-Wmaybe-uninitialized]
scratch.f90:28:30:

   28 |     end subroutine do_anything
      |                              ^
note: '.char2' was declared here

In OpenMP land, the parallel on its own defines the start of the parallel region. That’s the first problem; the parallel region just says: Run the enclosed code section with all threads. The second problem is that since char1 and char2 are initialized before the parallel region, the default behaviour is to enter the region uninitialized. Hence, if you re-initialize them (by uncommenting the code) the problem goes away.

You ought to use default(none) besides parallel, so that the compiler forces you to define everything explicitly.

One solution to the problem would be threadprivate variables:
Edit: x has the same problem with initialization, and has to be passed in with firstprivate instead:

module global_strings
  implicit none
  character(len=:), allocatable, save :: char1, char2
!$OMP THREADPRIVATE(char1, char2)
end module global_strings

program scratch
    use global_strings, only: char1, char2
    integer :: x
    x = 5
    char1 = 'test_char1'
    char2 = 'test_char2'
    print *, char2
    !$OMP parallel default(none) copyin(char1, char2) firstprivate(x)
    call do_anything(char1, x)
    call do_anything(char2, x)
    print *, x
    !$OMP end parallel
    ...

The output looks like this:

$ export OMP_NUM_THREADS=1
$ ./test
 test_char2
           20
$ export OMP_NUM_THREADS=2
$ ./test
 test_char2
           20
           20
3 Likes