This supports lowering parse-tree to MLIR for threadprivate directive
following the OpenMP 5.1 [2.21.2] standard. Take the following as an
example:
```
program m
integer, save :: i
!$omp threadprivate(i)
call sub(i)
!$omp parallel
call sub(i)
!$omp end parallel
end
```
```
func.func @_QQmain() {
%0 = fir.address_of(@_QFEi) : !fir.ref<i32>
%1 = omp.threadprivate %0 : !fir.ref<i32> -> !fir.ref<i32>
fir.call @_QPsub(%1) : (!fir.ref<i32>) -> ()
omp.parallel {
%2 = omp.threadprivate %0 : !fir.ref<i32> -> !fir.ref<i32>
fir.call @_QPsub(%2) : (!fir.ref<i32>) -> ()
omp.terminator
}
return
}
```
A threadprivate operation (omp.threadprivate) is created for all
references to a threadprivate variable. The runtime will appropriately
return a threadprivate var (%1 as above) or its copy (%2 as above)
depending on whether it is outside or inside a parallel region. For
threadprivate access outside the parallel region, the threadprivate
operation is created in instantiateVar. Inside the parallel region, it
is created in createBodyOfOp.
One new utility function collectSymbolSet is created for collecting
all the variables with a property within a evaluation, which may be one
Fortran, or OpenMP, or OpenACC construct.
Reviewed By: kiranchandramohan
Differential Revision: https://reviews.llvm.org/D124226
47 lines
2.7 KiB
Fortran
47 lines
2.7 KiB
Fortran
! This test checks lowering of OpenMP Threadprivate Directive.
|
|
! Test for character, array, and character array.
|
|
|
|
!RUN: %flang_fc1 -emit-fir -fopenmp %s -o - | FileCheck %s
|
|
|
|
module test
|
|
character :: x
|
|
integer :: y(5)
|
|
character(5) :: z(5)
|
|
|
|
!$omp threadprivate(x, y, z)
|
|
|
|
!CHECK-DAG: fir.global @_QMtestEx : !fir.char<1> {
|
|
!CHECK-DAG: fir.global @_QMtestEy : !fir.array<5xi32> {
|
|
!CHECK-DAG: fir.global @_QMtestEz : !fir.array<5x!fir.char<1,5>> {
|
|
|
|
contains
|
|
subroutine sub()
|
|
!CHECK-DAG: [[ADDR0:%.*]] = fir.address_of(@_QMtestEx) : !fir.ref<!fir.char<1>>
|
|
!CHECK-DAG: [[NEWADDR0:%.*]] = omp.threadprivate [[ADDR0]] : !fir.ref<!fir.char<1>> -> !fir.ref<!fir.char<1>>
|
|
!CHECK-DAG: [[ADDR1:%.*]] = fir.address_of(@_QMtestEy) : !fir.ref<!fir.array<5xi32>>
|
|
!CHECK-DAG: [[NEWADDR1:%.*]] = omp.threadprivate [[ADDR1]] : !fir.ref<!fir.array<5xi32>> -> !fir.ref<!fir.array<5xi32>>
|
|
!CHECK-DAG: [[ADDR2:%.*]] = fir.address_of(@_QMtestEz) : !fir.ref<!fir.array<5x!fir.char<1,5>>>
|
|
!CHECK-DAG: [[NEWADDR2:%.*]] = omp.threadprivate [[ADDR2]] : !fir.ref<!fir.array<5x!fir.char<1,5>>> -> !fir.ref<!fir.array<5x!fir.char<1,5>>>
|
|
!CHECK-DAG: %{{.*}} = fir.convert [[NEWADDR0]] : (!fir.ref<!fir.char<1>>) -> !fir.ref<i8>
|
|
!CHECK-DAG: %{{.*}} = fir.embox [[NEWADDR1]](%{{.*}}) : (!fir.ref<!fir.array<5xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<5xi32>>
|
|
!CHECK-DAG: %{{.*}} = fir.embox [[NEWADDR2]](%{{.*}}) : (!fir.ref<!fir.array<5x!fir.char<1,5>>>, !fir.shape<1>) -> !fir.box<!fir.array<5x!fir.char<1,5>>>
|
|
print *, x, y, z
|
|
|
|
!$omp parallel
|
|
!CHECK-DAG: [[ADDR33:%.*]] = omp.threadprivate [[ADDR0]] : !fir.ref<!fir.char<1>> -> !fir.ref<!fir.char<1>>
|
|
!CHECK-DAG: [[ADDR34:%.*]] = omp.threadprivate [[ADDR1]] : !fir.ref<!fir.array<5xi32>> -> !fir.ref<!fir.array<5xi32>>
|
|
!CHECK-DAG: [[ADDR35:%.*]] = omp.threadprivate [[ADDR2]] : !fir.ref<!fir.array<5x!fir.char<1,5>>> -> !fir.ref<!fir.array<5x!fir.char<1,5>>>
|
|
!CHECK-DAG: %{{.*}} = fir.convert [[ADDR33]] : (!fir.ref<!fir.char<1>>) -> !fir.ref<i8>
|
|
!CHECK-DAG: %{{.*}} = fir.embox [[ADDR34]](%{{.*}}) : (!fir.ref<!fir.array<5xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<5xi32>>
|
|
!CHECK-DAG: %{{.*}} = fir.embox [[ADDR35]](%{{.*}}) : (!fir.ref<!fir.array<5x!fir.char<1,5>>>, !fir.shape<1>) -> !fir.box<!fir.array<5x!fir.char<1,5>>>
|
|
print *, x, y, z
|
|
!$omp end parallel
|
|
|
|
!CHECK-DAG: %{{.*}} = fir.convert [[NEWADDR0]] : (!fir.ref<!fir.char<1>>) -> !fir.ref<i8>
|
|
!CHECK-DAG: %{{.*}} = fir.embox [[NEWADDR1]](%{{.*}}) : (!fir.ref<!fir.array<5xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<5xi32>>
|
|
!CHECK-DAG: %{{.*}} = fir.embox [[NEWADDR2]](%{{.*}}) : (!fir.ref<!fir.array<5x!fir.char<1,5>>>, !fir.shape<1>) -> !fir.box<!fir.array<5x!fir.char<1,5>>>
|
|
print *, x, y, z
|
|
|
|
end
|
|
end
|