13bfc5eb9SKiran Chandramohan! This test checks a few bug fixes in the PRIVATE clause lowering 23bfc5eb9SKiran Chandramohan 310df3207SKareem Ergawy! RUN: bbc -fopenmp -emit-hlfir %s -o - \ 410df3207SKareem Ergawy! RUN: | FileCheck %s 53bfc5eb9SKiran Chandramohan 610df3207SKareem Ergawy! CHECK: omp.private {type = private} @[[BOX_HEAP_CHAR_PRIVATIZER:_QFsub01Eaaa_private_ref_box_heap_c8xU]] : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> alloc { 710df3207SKareem Ergawy! CHECK: ^bb0(%[[ORIG_REF:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>): 810df3207SKareem Ergawy! CHECK: %[[VAL_4:.*]] = fir.alloca !fir.box<!fir.heap<!fir.char<1,?>>> {bindc_name = "aaa", pinned, uniq_name = "_QFsub01Eaaa"} 910df3207SKareem Ergawy! CHECK: %[[VAL_5:.*]] = fir.load %[[ORIG_REF]] : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> 1010df3207SKareem Ergawy! CHECK: %[[VAL_6:.*]] = fir.box_addr %[[VAL_5]] : (!fir.box<!fir.heap<!fir.char<1,?>>>) -> !fir.heap<!fir.char<1,?>> 1110df3207SKareem Ergawy! CHECK: %[[VAL_7:.*]] = fir.convert %[[VAL_6]] : (!fir.heap<!fir.char<1,?>>) -> i64 1210df3207SKareem Ergawy! CHECK: %[[VAL_8:.*]] = arith.constant 0 : i64 1310df3207SKareem Ergawy! CHECK: %[[VAL_9:.*]] = arith.cmpi ne, %[[VAL_7]], %[[VAL_8]] : i64 1410df3207SKareem Ergawy! CHECK: fir.if %[[VAL_9]] { 1510df3207SKareem Ergawy! CHECK: %[[ELEM_SIZE:.*]] = fir.box_elesize %{{.*}} : (!fir.box<!fir.heap<!fir.char<1,?>>>) -> index 1610df3207SKareem Ergawy! CHECK: %[[VAL_10:.*]] = arith.constant 0 : index 1710df3207SKareem Ergawy! CHECK: %[[VAL_11:.*]] = arith.cmpi sgt, %[[ELEM_SIZE]], %[[VAL_10]] : index 1810df3207SKareem Ergawy! CHECK: %[[VAL_12:.*]] = arith.select %[[VAL_11]], %[[ELEM_SIZE]], %[[VAL_10]] : index 1910df3207SKareem Ergawy! CHECK: %[[VAL_13:.*]] = fir.allocmem !fir.char<1,?>(%[[VAL_12]] : index) {fir.must_be_heap = true, uniq_name = "_QFsub01Eaaa.alloc"} 2010df3207SKareem Ergawy! CHECK: %[[VAL_14:.*]] = fir.embox %[[VAL_13]] typeparams %[[VAL_12]] : (!fir.heap<!fir.char<1,?>>, index) -> !fir.box<!fir.heap<!fir.char<1,?>>> 2110df3207SKareem Ergawy! CHECK: fir.store %[[VAL_14]] to %[[VAL_4]] : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> 2210df3207SKareem Ergawy! CHECK: } else { 2310df3207SKareem Ergawy! CHECK: %[[VAL_15:.*]] = fir.zero_bits !fir.heap<!fir.char<1,?>> 2410df3207SKareem Ergawy! CHECK: %[[VAL_16:.*]] = arith.constant 0 : index 2510df3207SKareem Ergawy! CHECK: %[[VAL_17:.*]] = fir.embox %[[VAL_15]] typeparams %[[VAL_16]] : (!fir.heap<!fir.char<1,?>>, index) -> !fir.box<!fir.heap<!fir.char<1,?>>> 2610df3207SKareem Ergawy! CHECK: fir.store %[[VAL_17]] to %[[VAL_4]] : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> 2710df3207SKareem Ergawy! CHECK: } 2810df3207SKareem Ergawy! CHECK: %[[VAL_18:.*]]:2 = hlfir.declare %[[VAL_4]] {fortran_attrs = #{{.*}}<allocatable>, uniq_name = "_QFsub01Eaaa"} : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) 2910df3207SKareem Ergawy!CHECK: omp.yield(%[[VAL_18]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) 3010df3207SKareem Ergawy!CHECK: } dealloc { 3110df3207SKareem Ergawy!CHECK: ^bb0(%[[ORIG_REF:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>): 3210df3207SKareem Ergawy! CHECK: %[[VAL_19:.*]] = fir.load %[[ORIG_REF]] : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> 3310df3207SKareem Ergawy! CHECK: %[[VAL_20:.*]] = fir.box_addr %[[VAL_19]] : (!fir.box<!fir.heap<!fir.char<1,?>>>) -> !fir.heap<!fir.char<1,?>> 3410df3207SKareem Ergawy! CHECK: %[[VAL_21:.*]] = fir.convert %[[VAL_20]] : (!fir.heap<!fir.char<1,?>>) -> i64 3510df3207SKareem Ergawy! CHECK: %[[VAL_22:.*]] = arith.constant 0 : i64 3610df3207SKareem Ergawy! CHECK: %[[VAL_23:.*]] = arith.cmpi ne, %[[VAL_21]], %[[VAL_22]] : i64 3710df3207SKareem Ergawy! CHECK: fir.if %[[VAL_23]] { 3810df3207SKareem Ergawy! CHECK: %[[VAL_24:.*]] = fir.load %[[ORIG_REF]] : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> 3910df3207SKareem Ergawy! CHECK: %[[VAL_25:.*]] = fir.box_addr %[[VAL_24]] : (!fir.box<!fir.heap<!fir.char<1,?>>>) -> !fir.heap<!fir.char<1,?>> 4010df3207SKareem Ergawy! CHECK: fir.freemem %[[VAL_25]] : !fir.heap<!fir.char<1,?>> 4110df3207SKareem Ergawy! CHECK: %[[VAL_26:.*]] = fir.zero_bits !fir.heap<!fir.char<1,?>> 4210df3207SKareem Ergawy! CHECK: %[[VAL_27:.*]] = arith.constant 0 : index 4310df3207SKareem Ergawy! CHECK: %[[VAL_28:.*]] = fir.embox %[[VAL_26]] typeparams %[[VAL_27]] : (!fir.heap<!fir.char<1,?>>, index) -> !fir.box<!fir.heap<!fir.char<1,?>>> 4410df3207SKareem Ergawy! CHECK: fir.store %[[VAL_28]] to %[[ORIG_REF]] : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> 4510df3207SKareem Ergawy!CHECK: } 4610df3207SKareem Ergawy!CHECK: omp.yield 4710df3207SKareem Ergawy!CHECK: } 4810df3207SKareem Ergawy 4910df3207SKareem Ergawy! CHECK-LABEL: @_QPmultiple_private_fix( 503bfc5eb9SKiran Chandramohan! CHECK-SAME: %[[GAMA:.*]]: !fir.ref<i32> {fir.bindc_name = "gama"} 511710c8cfSSlava Zakharin! CHECK-DAG: %[[GAMA_DECL:.*]]:2 = hlfir.declare %[[GAMA]] dummy_scope %{{[0-9]+}} {uniq_name = "_QFmultiple_private_fixEgama"} : (!fir.ref<i32>, !fir.dscope) -> (!fir.ref<i32>, !fir.ref<i32>) 52a4deb14eSKiran Chandramohan! CHECK-DAG: %[[VAL_0:.*]] = fir.alloca i32 {bindc_name = "i", uniq_name = "_QFmultiple_private_fixEi"} 53a4deb14eSKiran Chandramohan! CHECK-DAG: %[[I_DECL:.*]]:2 = hlfir.declare %[[VAL_0]] {uniq_name = "_QFmultiple_private_fixEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 54a4deb14eSKiran Chandramohan! CHECK-DAG: %[[VAL_1:.*]] = fir.alloca i32 {bindc_name = "j", uniq_name = "_QFmultiple_private_fixEj"} 55a4deb14eSKiran Chandramohan! CHECK-DAG: %[[J_DECL:.*]]:2 = hlfir.declare %[[VAL_1]] {uniq_name = "_QFmultiple_private_fixEj"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 56a4deb14eSKiran Chandramohan! CHECK-DAG: %[[VAL_2:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFmultiple_private_fixEx"} 57a4deb14eSKiran Chandramohan! CHECK-DAG: %[[X_DECL:.*]]:2 = hlfir.declare %[[VAL_2]] {uniq_name = "_QFmultiple_private_fixEx"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 583bfc5eb9SKiran Chandramohan! CHECK: omp.parallel { 59*937cbce1SKareem Ergawy! CHECK-DAG: %[[PRIV_I:.*]] = fir.alloca i32 {bindc_name = "i", pinned, {{.*}}} 60*937cbce1SKareem Ergawy! CHECK-DAG: %[[PRIV_I_DECL:.*]]:2 = hlfir.declare %[[PRIV_I]] {uniq_name = "_QFmultiple_private_fixEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 61*937cbce1SKareem Ergawy! CHECK-DAG: %[[PRIV_J:.*]] = fir.alloca i32 {bindc_name = "j", pinned, uniq_name = "_QFmultiple_private_fixEj"} 62*937cbce1SKareem Ergawy! CHECK-DAG: %[[PRIV_J_DECL:.*]]:2 = hlfir.declare %[[PRIV_J]] {uniq_name = "_QFmultiple_private_fixEj"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 63*937cbce1SKareem Ergawy! CHECK-DAG: %[[PRIV_X:.*]] = fir.alloca i32 {bindc_name = "x", pinned, {{.*}}} 64*937cbce1SKareem Ergawy! CHECK-DAG: %[[PRIV_X_DECL:.*]]:2 = hlfir.declare %[[PRIV_X]] {uniq_name = "_QFmultiple_private_fixEx"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 653bfc5eb9SKiran Chandramohan! CHECK: %[[ONE:.*]] = arith.constant 1 : i32 663bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_3:.*]] = fir.load %[[GAMA_DECL]]#0 : !fir.ref<i32> 673bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_5:.*]] = arith.constant 1 : i32 68*937cbce1SKareem Ergawy! CHECK: omp.wsloop { 69ca4dbc27SSergio Afonso! CHECK-NEXT: omp.loop_nest (%[[VAL_6:.*]]) : i32 = (%[[ONE]]) to (%[[VAL_3]]) inclusive step (%[[VAL_5]]) { 703bfc5eb9SKiran Chandramohan! CHECK: fir.store %[[VAL_6]] to %[[PRIV_I_DECL]]#1 : !fir.ref<i32> 713bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_7:.*]] = arith.constant 1 : i32 723bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_8:.*]] = fir.convert %[[VAL_7]] : (i32) -> index 733bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_9:.*]] = fir.load %[[GAMA_DECL]]#0 : !fir.ref<i32> 743bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_10:.*]] = fir.convert %[[VAL_9]] : (i32) -> index 753bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_11:.*]] = arith.constant 1 : index 763bfc5eb9SKiran Chandramohan! CHECK: %[[LB:.*]] = fir.convert %[[VAL_8]] : (index) -> i32 773bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_12:.*]]:2 = fir.do_loop %[[VAL_13:[^ ]*]] = 783bfc5eb9SKiran Chandramohan! CHECK-SAME: %[[VAL_8]] to %[[VAL_10]] step %[[VAL_11]] 793bfc5eb9SKiran Chandramohan! CHECK-SAME: iter_args(%[[IV:.*]] = %[[LB]]) -> (index, i32) { 803bfc5eb9SKiran Chandramohan! CHECK: fir.store %[[IV]] to %[[PRIV_J_DECL]]#1 : !fir.ref<i32> 813bfc5eb9SKiran Chandramohan! CHECK: %[[LOAD:.*]] = fir.load %[[PRIV_I_DECL]]#0 : !fir.ref<i32> 823bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_15:.*]] = fir.load %[[PRIV_J_DECL]]#0 : !fir.ref<i32> 833bfc5eb9SKiran Chandramohan! CHECK: %[[VAL_16:.*]] = arith.addi %[[LOAD]], %[[VAL_15]] : i32 843bfc5eb9SKiran Chandramohan! CHECK: hlfir.assign %[[VAL_16]] to %[[PRIV_X_DECL]]#0 : i32, !fir.ref<i32> 85a88677edSYusuke MINATO! CHECK: %[[VAL_17:.*]] = arith.addi %[[VAL_13]], %[[VAL_11]] overflow<nsw> : index 863bfc5eb9SKiran Chandramohan! CHECK: %[[STEPCAST:.*]] = fir.convert %[[VAL_11]] : (index) -> i32 873bfc5eb9SKiran Chandramohan! CHECK: %[[IVLOAD:.*]] = fir.load %[[PRIV_J_DECL]]#1 : !fir.ref<i32> 88a88677edSYusuke MINATO! CHECK: %[[IVINC:.*]] = arith.addi %[[IVLOAD]], %[[STEPCAST]] overflow<nsw> : 893bfc5eb9SKiran Chandramohan! CHECK: fir.result %[[VAL_17]], %[[IVINC]] : index, i32 903bfc5eb9SKiran Chandramohan! CHECK: } 913bfc5eb9SKiran Chandramohan! CHECK: fir.store %[[VAL_12]]#1 to %[[PRIV_J_DECL]]#1 : !fir.ref<i32> 923bfc5eb9SKiran Chandramohan! CHECK: omp.yield 933bfc5eb9SKiran Chandramohan! CHECK: } 943bfc5eb9SKiran Chandramohan! CHECK: } 95ca4dbc27SSergio Afonso! CHECK: omp.terminator 96ca4dbc27SSergio Afonso! CHECK: } 973bfc5eb9SKiran Chandramohan! CHECK: return 983bfc5eb9SKiran Chandramohansubroutine multiple_private_fix(gama) 993bfc5eb9SKiran Chandramohan integer :: i, j, x, gama 1003bfc5eb9SKiran Chandramohan!$OMP PARALLEL DO PRIVATE(j,x) 1013bfc5eb9SKiran Chandramohan do i = 1, gama 1023bfc5eb9SKiran Chandramohan do j = 1, gama 1033bfc5eb9SKiran Chandramohan x = i + j 1043bfc5eb9SKiran Chandramohan end do 1053bfc5eb9SKiran Chandramohan end do 1063bfc5eb9SKiran Chandramohan!$OMP END PARALLEL DO 1073bfc5eb9SKiran Chandramohanend subroutine 1083bfc5eb9SKiran Chandramohan 1093bfc5eb9SKiran Chandramohan! CHECK-LABEL: multiple_private_fix2 1103bfc5eb9SKiran Chandramohan! CHECK: %[[X1:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFmultiple_private_fix2Ex"} 1113bfc5eb9SKiran Chandramohan! CHECK: %[[X1_DECL:.*]]:2 = hlfir.declare %[[X1]] {uniq_name = "_QFmultiple_private_fix2Ex"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 11210df3207SKareem Ergawy! CHECK: omp.parallel private({{.*}} {{.*}}#0 -> %[[X2:.*]] : {{.*}}) { 1133bfc5eb9SKiran Chandramohan! CHECK: %[[X2_DECL:.*]]:2 = hlfir.declare %[[X2]] {uniq_name = "_QFmultiple_private_fix2Ex"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 11410df3207SKareem Ergawy! CHECK: omp.parallel private({{.*}} {{.*}}#0 -> %[[X3:.*]] : {{.*}}) { 1153bfc5eb9SKiran Chandramohan! CHECK: %[[X3_DECL:.*]]:2 = hlfir.declare %[[X3]] {uniq_name = "_QFmultiple_private_fix2Ex"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 1163bfc5eb9SKiran Chandramohan! CHECK: %[[C3:.*]] = arith.constant 1 : i32 1173bfc5eb9SKiran Chandramohan! CHECK: hlfir.assign %[[C3]] to %[[X3_DECL]]#0 : i32, !fir.ref<i32> 1183bfc5eb9SKiran Chandramohan! CHECK: omp.terminator 1193bfc5eb9SKiran Chandramohan! CHECK: } 1203bfc5eb9SKiran Chandramohan! CHECK: %[[C2:.*]] = arith.constant 1 : i32 1213bfc5eb9SKiran Chandramohan! CHECK: hlfir.assign %[[C2]] to %[[X2_DECL]]#0 : i32, !fir.ref<i32> 1223bfc5eb9SKiran Chandramohan! CHECK: omp.terminator 1233bfc5eb9SKiran Chandramohan! CHECK: } 1243bfc5eb9SKiran Chandramohan! CHECK: %[[C1:.*]] = arith.constant 1 : i32 1253bfc5eb9SKiran Chandramohan! CHECK: hlfir.assign %[[C1]] to %[[X1_DECL]]#0 : i32, !fir.ref<i32> 1263bfc5eb9SKiran Chandramohan! CHECK: return 1273bfc5eb9SKiran Chandramohansubroutine multiple_private_fix2() 1283bfc5eb9SKiran Chandramohan integer :: x 1293bfc5eb9SKiran Chandramohan !$omp parallel private(x) 1303bfc5eb9SKiran Chandramohan !$omp parallel private(x) 1313bfc5eb9SKiran Chandramohan x = 1 1323bfc5eb9SKiran Chandramohan !$omp end parallel 1333bfc5eb9SKiran Chandramohan x = 1 1343bfc5eb9SKiran Chandramohan !$omp end parallel 1353bfc5eb9SKiran Chandramohan x = 1 1363bfc5eb9SKiran Chandramohanend subroutine 13757d0d3b4SKiran Chandramohan 13857d0d3b4SKiran Chandramohan 13957d0d3b4SKiran Chandramohan! CHECK-LABEL: func.func @_QPsub01( 14057d0d3b4SKiran Chandramohan! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> {fir.bindc_name = "aaa"}) { 14157d0d3b4SKiran Chandramohan! CHECK: %[[VAL_1:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> 14257d0d3b4SKiran Chandramohan! CHECK: %[[VAL_2:.*]] = fir.box_elesize %[[VAL_1]] : (!fir.box<!fir.heap<!fir.char<1,?>>>) -> index 1431710c8cfSSlava Zakharin! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_0]] typeparams %[[VAL_2]] dummy_scope %{{[0-9]+}} {fortran_attrs = #{{.*}}<allocatable>, uniq_name = "_QFsub01Eaaa"} : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, index, !fir.dscope) -> (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) 14410df3207SKareem Ergawy! CHECK: omp.parallel private(@[[BOX_HEAP_CHAR_PRIVATIZER]] %[[VAL_3]]#0 -> %{{.*}} : {{.*}}) { 14557d0d3b4SKiran Chandramohan! CHECK: omp.terminator 14657d0d3b4SKiran Chandramohan! CHECK: } 14757d0d3b4SKiran Chandramohan! CHECK: return 14857d0d3b4SKiran Chandramohan! CHECK: } 14957d0d3b4SKiran Chandramohan 15057d0d3b4SKiran Chandramohansubroutine sub01(aaa) 15157d0d3b4SKiran Chandramohan character(*),allocatable :: aaa 15257d0d3b4SKiran Chandramohan !$omp parallel private(aaa) 15357d0d3b4SKiran Chandramohan !$omp end parallel 15457d0d3b4SKiran Chandramohanend subroutine 15557d0d3b4SKiran Chandramohan 15657d0d3b4SKiran Chandramohan! CHECK-LABEL: func.func @_QPsub02( 15757d0d3b4SKiran Chandramohan! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>> {fir.bindc_name = "bbb"}) { 1581710c8cfSSlava Zakharin! CHECK: %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] dummy_scope %{{[0-9]+}} {fortran_attrs = #{{.*}}<allocatable>, uniq_name = "_QFsub02Ebbb"} : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, !fir.dscope) -> (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>, !fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) 15910df3207SKareem Ergawy! CHECK: omp.parallel private(@{{.*}} %[[VAL_1]]#0 -> %[[PRIV_ARG:.*]] : {{.*}}) { 16010df3207SKareem Ergawy! CHECK: %{{.*}}:2 = hlfir.declare %[[PRIV_ARG]] {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QFsub02Ebbb"} : (!fir.ref<!fir.box<!fir.heap<!fir.char<1,?>>>>) 16157d0d3b4SKiran Chandramohan! CHECK: omp.terminator 16257d0d3b4SKiran Chandramohan! CHECK: } 16357d0d3b4SKiran Chandramohan! CHECK: return 16457d0d3b4SKiran Chandramohan! CHECK: } 16557d0d3b4SKiran Chandramohan 16657d0d3b4SKiran Chandramohansubroutine sub02(bbb) 16757d0d3b4SKiran Chandramohan character(:),allocatable :: bbb 16857d0d3b4SKiran Chandramohan !$omp parallel private(bbb) 16957d0d3b4SKiran Chandramohan !$omp end parallel 17057d0d3b4SKiran Chandramohanend subroutine sub02 17157d0d3b4SKiran Chandramohan 172