xref: /llvm-project/flang/test/Lower/OpenMP/associate.f90 (revision 937cbce14c9aa956342a9c818c26a8a557802843)
1! Check that constructs with associate and variables that have implicitly
2! determined DSAs are lowered properly.
3! RUN: %flang_fc1 -emit-hlfir -fopenmp -o - %s 2>&1 | FileCheck %s
4
5!CHECK-LABEL: func @_QPtest_parallel_assoc
6!CHECK:         omp.parallel {
7!CHECK-NOT:       hlfir.declare {{.*}} {uniq_name = "_QFtest_parallel_assocEa"}
8!CHECK-NOT:       hlfir.declare {{.*}} {uniq_name = "_QFtest_parallel_assocEb"}
9!CHECK:           omp.wsloop {
10!CHECK:           }
11!CHECK:         }
12!CHECK:         omp.parallel {{.*}} {
13!CHECK-NOT:       hlfir.declare {{.*}} {uniq_name = "_QFtest_parallel_assocEb"}
14!CHECK:           omp.wsloop {
15!CHECK:           }
16!CHECK:         }
17subroutine test_parallel_assoc()
18  integer, parameter :: l = 3
19  integer :: a(l)
20  integer :: i
21  a = 1
22
23  !$omp parallel do
24  do i = 1,l
25    associate (b=>a)
26      b(i) = b(i) * 2
27    end associate
28  enddo
29  !$omp end parallel do
30
31  !$omp parallel do default(private)
32  do i = 1,l
33    associate (b=>a)
34      b(i) = b(i) * 2
35    end associate
36  enddo
37  !$omp end parallel do
38end subroutine
39