
Currently Statement context used during processing of clauses is finalized after the OpenMP operation creation. This causes the finalization to go inside the OpenMP region and this can lead to multiple finalizations in a parallel region. This fix proposes to finalize them before the OpenMP op creation. Fixes #71342
13 lines
287 B
Fortran
13 lines
287 B
Fortran
!RUN: %flang_fc1 -emit-hlfir -fopenmp %s -o - | FileCheck %s
|
|
|
|
!CHECK-LABEL: func @_QPtest1
|
|
subroutine test1(a)
|
|
integer :: a(:,:)
|
|
!CHECK: hlfir.destroy
|
|
!CHECK: omp.parallel if
|
|
!$omp parallel if(any(a .eq. 1))
|
|
!CHECK-NOT: hlfir.destroy
|
|
print *, "Hello"
|
|
!$omp end parallel
|
|
end subroutine
|