1! Simple test for lowering of OpenMP Threadprivate Directive with HLFIR. 2 3!RUN: %flang_fc1 -flang-experimental-hlfir -emit-hlfir -fopenmp %s -o - | FileCheck %s 4!RUN: bbc -hlfir -emit-hlfir -fopenmp %s -o - | FileCheck %s 5 6!CHECK-LABEL: @_QPsub 7!CHECK: %[[ADDR:.*]] = fir.address_of(@_QFsubEa) : !fir.ref<i32> 8!CHECK: %[[DECL:.*]]:2 = hlfir.declare %[[ADDR]] {uniq_name = "_QFsubEa"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 9!CHECK: %[[TP:.*]] = omp.threadprivate %[[DECL]]#1 : !fir.ref<i32> -> !fir.ref<i32> 10!CHECK: %[[TP_DECL:.*]]:2 = hlfir.declare %[[TP:.*]] {uniq_name = "_QFsubEa"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 11!CHECK: omp.parallel { 12!CHECK: %[[TP_PARALLEL:.*]] = omp.threadprivate %[[DECL]]#1 : !fir.ref<i32> -> !fir.ref<i32> 13!CHECK: %[[TP_PARALLEL_DECL:.*]]:2 = hlfir.declare %[[TP_PARALLEL]] {uniq_name = "_QFsubEa"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 14!CHECK: %[[TP_VAL:.*]] = fir.load %[[TP_PARALLEL_DECL]]#0 : !fir.ref<i32> 15!CHECK: %{{.*}} = fir.call @_FortranAioOutputInteger32(%{{.*}}, %[[TP_VAL]]) fastmath<contract> : (!fir.ref<i8>, i32) -> i1 16!CHECK: omp.terminator 17 18!CHECK: fir.global internal @_QFsubEa : i32 19 20subroutine sub() 21 integer, save:: a 22 !$omp threadprivate(a) 23 !$omp parallel 24 print *, a 25 !$omp end parallel 26end subroutine 27 28