
Remove the `openmp` prefix from delayed privatization/localization flags since they are now used for `do concurrent` as well. PR stack: - https://github.com/llvm/llvm-project/pull/137928 - https://github.com/llvm/llvm-project/pull/138505 - https://github.com/llvm/llvm-project/pull/138506 - https://github.com/llvm/llvm-project/pull/138512 - https://github.com/llvm/llvm-project/pull/138534 - https://github.com/llvm/llvm-project/pull/138816 (this PR)
29 lines
786 B
Fortran
29 lines
786 B
Fortran
! Test early privatization for multiple allocatable variables.
|
|
|
|
! RUN: %flang_fc1 -emit-hlfir -fopenmp -mmlir --enable-delayed-privatization=false \
|
|
! RUN: -o - %s 2>&1 | FileCheck %s
|
|
|
|
! RUN: bbc -emit-hlfir -fopenmp --enable-delayed-privatization=false -o - %s 2>&1 |\
|
|
! RUN: FileCheck %s
|
|
|
|
subroutine delayed_privatization_allocatable
|
|
implicit none
|
|
integer, allocatable :: var1, var2
|
|
|
|
!$omp parallel private(var1, var2)
|
|
var1 = 10
|
|
var2 = 20
|
|
!$omp end parallel
|
|
end subroutine
|
|
|
|
! Verify that private versions of each variable are both allocated and freed
|
|
! within the parallel region.
|
|
|
|
! CHECK: omp.parallel {
|
|
! CHECK: fir.allocmem
|
|
! CHECK: fir.allocmem
|
|
! CHECK: fir.freemem
|
|
! CHECK: fir.freemem
|
|
! CHECK: omp.terminator
|
|
! CHECK-NEXT: }
|