The code below uses a derived type, Vec, with an allocatable component. In the OpenMP parallel region, a private variable A of type Vec is allocated and deallocated.
This code with the openmp compiler flag runs fine with gfortran. However, it crashes with ifx (version 2022.0.0) when A is deallocated.
PROGRAM test_omp
USE, intrinsic :: ISO_FORTRAN_ENV, ONLY : rk => real64
!$ USE omp_lib, only : OMP_GET_THREAD_NUM
IMPLICIT NONE
TYPE Vec
integer, allocatable :: V(:)
END TYPE Vec
type (Vec), allocatable :: A(:)
integer :: i
!$OMP PARALLEL DEFAULT(NONE) &
!$OMP PRIVATE(i,A) &
!$OMP NUM_THREADS(2)
allocate(A(2))
write(*,*) 'allocate A',OMP_GET_THREAD_NUM()
DO i=1,size(A)
allocate(A(i)%V(2))
A(i)%V = 10*i + OMP_GET_THREAD_NUM()
END DO
write(*,*) 'A',(A(i)%V,i=1,size(A))
DO i=1,size(A)
deallocate(A(i)%V)
END DO
deallocate(A)
write(*,*) 'deallocate A',OMP_GET_THREAD_NUM()
!$OMP END PARALLEL
END PROGRAM test_omp
With ifx (ifx -O0 -qopenmp), it gives:
allocate A 0
allocate A 1
A 10 10 20 20
A 11 11 21 21
deallocate A 0
deallocate A 1
forrtl: severe (153): allocatable array or pointer is not allocated
I would question if PRIVATE A can be deallocated, given on exit from the !$OMP region, it would be removed ?
You assume gFortran is ok with this, although I don’t know.
Was the program exiting the !$OMP region before the error, or is it related to DEALLOCATE ?
Where I have allocated an allocatable array, I have not considered how this private array that is allocated in the !$OMP region is finally disposed of.
I have not used derived types in this situation.
My preferred approach where a prior unknown size array is required has been to call a routine and generate an automatic array, on the thread stack. I have mainly done this to place private arrays on the stack, as private allocated arrays go on the heap.
Have you considered OpenMP Ver 5 array management ? although I have not used this approach.
I includes reporting from stat=stat, but saw no indication of error with gFortran 11.1
PROGRAM test_omp
USE, intrinsic :: ISO_FORTRAN_ENV, ONLY : rk => real64
!$ USE omp_lib, only : OMP_GET_THREAD_NUM
IMPLICIT NONE
TYPE Vec
integer, allocatable :: V(:)
END TYPE Vec
type (Vec), allocatable :: A(:)
integer :: i,stat,id
!$OMP PARALLEL DEFAULT(NONE) &
!$OMP PRIVATE(i,A,stat,id) &
!$OMP NUM_THREADS(2)
id = OMP_GET_THREAD_NUM()
allocate(A(2),stat=stat)
write(*,12) id,' allocate A stat = ',stat
DO i=1,size(A)
allocate(A(i)%V(2))
A(i)%V = 10*i + id
END DO
write(*,12) id,' A%V = ',(A(i)%V,i=1,size(A))
DO i=1,size(A)
deallocate (A(i)%V,stat=stat)
write(*,13) id,i,' deallocate A%V stat = ',stat
END DO
deallocate (A,stat=stat)
write(*,12) id, ' deallocate A stat = ',stat
!$OMP END PARALLEL
write (*,*) ' outside OMP'
12 format ( i4,a,4i5)
13 format ( 2i4,a,i5)
END PROGRAM test_omp
With ifx and your code with the stat. I still get the same error. The error is coming when the code exits the OpenMP region. The deallocation is fine.
0 allocate A stat = 0
1 allocate A stat = 0
0 A%V = 10 10 20 20
1 A%V = 11 11 21 21
0 1 deallocate A%V stat = 0
1 1 deallocate A%V stat = 0
0 2 deallocate A%V stat = 0
1 2 deallocate A%V stat = 0
0 deallocate A stat = 0
1 deallocate A stat = 0
forrtl: severe (153): allocatable array or pointer is not allocated