File: threadprivate-char-array-chararray.f90

package info (click to toggle)
llvm-toolchain-19 1%3A19.1.7-3
  • links: PTS, VCS
  • area: main
  • in suites: trixie
  • size: 1,998,520 kB
  • sloc: cpp: 6,951,680; ansic: 1,486,157; asm: 913,598; python: 232,024; f90: 80,126; objc: 75,281; lisp: 37,276; pascal: 16,990; sh: 10,009; ml: 5,058; perl: 4,724; awk: 3,523; makefile: 3,167; javascript: 2,504; xml: 892; fortran: 664; cs: 573
file content (54 lines) | stat: -rw-r--r-- 4,730 bytes parent folder | download | duplicates (9)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
! This test checks lowering of OpenMP Threadprivate Directive.
! Test for character, array, and character array.

!RUN: %flang_fc1 -emit-hlfir -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:  %[[X:.*]] = fir.address_of(@_QMtestEx) : !fir.ref<!fir.char<1>>
!CHECK-DAG:  %[[X_DECL:.*]]:2 = hlfir.declare %[[X]] typeparams %c1 {uniq_name = "_QMtestEx"} : (!fir.ref<!fir.char<1>>, index) -> (!fir.ref<!fir.char<1>>, !fir.ref<!fir.char<1>>)
!CHECK-DAG:  %[[OMP_X:.*]] = omp.threadprivate %[[X_DECL]]#1 : !fir.ref<!fir.char<1>> -> !fir.ref<!fir.char<1>>
!CHECK-DAG:  %[[OMP_X_DECL:.*]]:2 = hlfir.declare %[[OMP_X]] typeparams %c1 {uniq_name = "_QMtestEx"} : (!fir.ref<!fir.char<1>>, index) -> (!fir.ref<!fir.char<1>>, !fir.ref<!fir.char<1>>)
!CHECK-DAG:  %[[Y:.*]] = fir.address_of(@_QMtestEy) : !fir.ref<!fir.array<5xi32>>
!CHECK-DAG:  %[[Y_DECL:.*]]:2 = hlfir.declare %[[Y]](%{{.*}}) {uniq_name = "_QMtestEy"} : (!fir.ref<!fir.array<5xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<5xi32>>, !fir.ref<!fir.array<5xi32>>)
!CHECK-DAG:  %[[OMP_Y:.*]] = omp.threadprivate %[[Y_DECL]]#1 : !fir.ref<!fir.array<5xi32>> -> !fir.ref<!fir.array<5xi32>>
!CHECK-DAG:  %[[OMP_Y_DECL:.*]]:2 = hlfir.declare %[[OMP_Y]](%{{.*}}) {uniq_name = "_QMtestEy"} : (!fir.ref<!fir.array<5xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<5xi32>>, !fir.ref<!fir.array<5xi32>>)
!CHECK-DAG:  %[[Z:.*]] = fir.address_of(@_QMtestEz) : !fir.ref<!fir.array<5x!fir.char<1,5>>>
!CHECK-DAG:  %[[Z_DECL:.*]]:2 = hlfir.declare %[[Z]](%{{.*}}) typeparams %c5_0 {uniq_name = "_QMtestEz"} : (!fir.ref<!fir.array<5x!fir.char<1,5>>>, !fir.shape<1>, index) -> (!fir.ref<!fir.array<5x!fir.char<1,5>>>, !fir.ref<!fir.array<5x!fir.char<1,5>>>)
!CHECK-DAG:  %[[OMP_Z:.*]] = omp.threadprivate %[[Z_DECL]]#1 : !fir.ref<!fir.array<5x!fir.char<1,5>>> -> !fir.ref<!fir.array<5x!fir.char<1,5>>>
!CHECK-DAG:  %[[OMP_Z_DECL:.*]]:2 = hlfir.declare %[[OMP_Z]](%{{.*}}) typeparams %c5_0 {uniq_name = "_QMtestEz"} : (!fir.ref<!fir.array<5x!fir.char<1,5>>>, !fir.shape<1>, index) -> (!fir.ref<!fir.array<5x!fir.char<1,5>>>, !fir.ref<!fir.array<5x!fir.char<1,5>>>)
!CHECK-DAG:  %{{.*}} = fir.convert %[[OMP_X_DECL]]#1 : (!fir.ref<!fir.char<1>>) -> !fir.ref<i8>
!CHECK-DAG:  %{{.*}} = fir.embox %[[OMP_Y_DECL]]#1(%{{.*}}) : (!fir.ref<!fir.array<5xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<5xi32>>
!CHECK-DAG:  %{{.*}} = fir.embox %[[OMP_Z_DECL]]#1(%{{.*}}) : (!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:  %[[X_PVT:.*]] = omp.threadprivate %[[X_DECL]]#1 : !fir.ref<!fir.char<1>> -> !fir.ref<!fir.char<1>>
!CHECK-DAG:  %[[X_PVT_DECL:.*]]:2 = hlfir.declare %[[X_PVT]] typeparams %c1 {uniq_name = "_QMtestEx"} : (!fir.ref<!fir.char<1>>, index) -> (!fir.ref<!fir.char<1>>, !fir.ref<!fir.char<1>>)
!CHECK-DAG:  %[[Y_PVT:.*]] = omp.threadprivate %[[Y_DECL]]#1 : !fir.ref<!fir.array<5xi32>> -> !fir.ref<!fir.array<5xi32>>
!CHECK-DAG:  %[[Y_PVT_DECL:.*]]:2 = hlfir.declare %[[Y_PVT]](%{{.*}}) {uniq_name = "_QMtestEy"} : (!fir.ref<!fir.array<5xi32>>, !fir.shape<1>) -> (!fir.ref<!fir.array<5xi32>>, !fir.ref<!fir.array<5xi32>>)
!CHECK-DAG:  %[[Z_PVT:.*]] = omp.threadprivate %[[Z_DECL]]#1 : !fir.ref<!fir.array<5x!fir.char<1,5>>> -> !fir.ref<!fir.array<5x!fir.char<1,5>>>
!CHECK-DAG:  %[[Z_PVT_DECL:.*]]:2 = hlfir.declare %[[Z_PVT]](%{{.*}}) typeparams %c5_0 {uniq_name = "_QMtestEz"} : (!fir.ref<!fir.array<5x!fir.char<1,5>>>, !fir.shape<1>, index) -> (!fir.ref<!fir.array<5x!fir.char<1,5>>>, !fir.ref<!fir.array<5x!fir.char<1,5>>>)
!CHECK-DAG:  %{{.*}} = fir.convert %[[X_PVT_DECL]]#1 : (!fir.ref<!fir.char<1>>) -> !fir.ref<i8>
!CHECK-DAG:  %{{.*}} = fir.embox %[[Y_PVT_DECL]]#1(%{{.*}}) : (!fir.ref<!fir.array<5xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<5xi32>>
!CHECK-DAG:  %{{.*}} = fir.embox %[[Z_PVT_DECL]]#1(%{{.*}}) : (!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 %[[OMP_X_DECL]]#1 : (!fir.ref<!fir.char<1>>) -> !fir.ref<i8>
!CHECK-DAG:  %{{.*}} = fir.embox %[[OMP_Y_DECL]]#1(%{{.*}}) : (!fir.ref<!fir.array<5xi32>>, !fir.shape<1>) -> !fir.box<!fir.array<5xi32>>
!CHECK-DAG:  %{{.*}} = fir.embox %[[OMP_Z_DECL]]#1(%{{.*}}) : (!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