1! Test LASTPRIVATE with iteration variable. 2! RUN: %flang_fc1 -emit-hlfir -fopenmp -o - %s 2>&1 | FileCheck %s 3 4!CHECK-LABEL: func @_QPlastprivate_iv_inc 5 6!CHECK: %[[I2_MEM:.*]] = fir.alloca i32 {bindc_name = "i", uniq_name = "_QFlastprivate_iv_incEi"} 7!CHECK: %[[I2:.*]]:2 = hlfir.declare %[[I2_MEM]] {uniq_name = "_QFlastprivate_iv_incEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 8 9!CHECK: %[[I_MEM:.*]] = fir.alloca i32 {bindc_name = "i", pinned, {{.*}}} 10!CHECK: %[[I:.*]]:2 = hlfir.declare %[[I_MEM]] {uniq_name = "_QFlastprivate_iv_incEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 11 12!CHECK: %[[LB:.*]] = arith.constant 4 : i32 13!CHECK: %[[UB:.*]] = arith.constant 10 : i32 14!CHECK: %[[STEP:.*]] = arith.constant 3 : i32 15!CHECK: omp.wsloop { 16!CHECK-NEXT: omp.loop_nest (%[[IV:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) { 17!CHECK: fir.store %[[IV]] to %[[I]]#1 : !fir.ref<i32> 18!CHECK: %[[V:.*]] = arith.addi %[[IV]], %[[STEP]] : i32 19!CHECK: %[[C0:.*]] = arith.constant 0 : i32 20!CHECK: %[[STEP_NEG:.*]] = arith.cmpi slt, %[[STEP]], %[[C0]] : i32 21!CHECK: %[[V_LT:.*]] = arith.cmpi slt, %[[V]], %[[UB]] : i32 22!CHECK: %[[V_GT:.*]] = arith.cmpi sgt, %[[V]], %[[UB]] : i32 23!CHECK: %[[CMP:.*]] = arith.select %[[STEP_NEG]], %[[V_LT]], %[[V_GT]] : i1 24!CHECK: fir.if %[[CMP]] { 25!CHECK: fir.store %[[V]] to %[[I]]#1 : !fir.ref<i32> 26!CHECK: %[[I_VAL:.*]] = fir.load %[[I]]#0 : !fir.ref<i32> 27!CHECK: hlfir.assign %[[I_VAL]] to %[[I2]]#0 : i32, !fir.ref<i32> 28!CHECK: } 29!CHECK: omp.yield 30!CHECK: } 31!CHECK: } 32subroutine lastprivate_iv_inc() 33 integer :: i 34 35 !$omp do lastprivate(i) 36 do i = 4, 10, 3 37 end do 38 !$omp end do 39end subroutine 40 41!CHECK-LABEL: func @_QPlastprivate_iv_dec 42 43!CHECK: %[[I2_MEM:.*]] = fir.alloca i32 {bindc_name = "i", uniq_name = "_QFlastprivate_iv_decEi"} 44!CHECK: %[[I2:.*]]:2 = hlfir.declare %[[I2_MEM]] {uniq_name = "_QFlastprivate_iv_decEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 45 46!CHECK: %[[I_MEM:.*]] = fir.alloca i32 {bindc_name = "i", pinned, {{.*}}} 47!CHECK: %[[I:.*]]:2 = hlfir.declare %[[I_MEM]] {uniq_name = "_QFlastprivate_iv_decEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>) 48 49!CHECK: %[[LB:.*]] = arith.constant 10 : i32 50!CHECK: %[[UB:.*]] = arith.constant 1 : i32 51!CHECK: %[[STEP:.*]] = arith.constant -3 : i32 52!CHECK: omp.wsloop { 53!CHECK-NEXT: omp.loop_nest (%[[IV:.*]]) : i32 = (%[[LB]]) to (%[[UB]]) inclusive step (%[[STEP]]) { 54!CHECK: fir.store %[[IV]] to %[[I]]#1 : !fir.ref<i32> 55!CHECK: %[[V:.*]] = arith.addi %[[IV]], %[[STEP]] : i32 56!CHECK: %[[C0:.*]] = arith.constant 0 : i32 57!CHECK: %[[STEP_NEG:.*]] = arith.cmpi slt, %[[STEP]], %[[C0]] : i32 58!CHECK: %[[V_LT:.*]] = arith.cmpi slt, %[[V]], %[[UB]] : i32 59!CHECK: %[[V_GT:.*]] = arith.cmpi sgt, %[[V]], %[[UB]] : i32 60!CHECK: %[[CMP:.*]] = arith.select %[[STEP_NEG]], %[[V_LT]], %[[V_GT]] : i1 61!CHECK: fir.if %[[CMP]] { 62!CHECK: fir.store %[[V]] to %[[I]]#1 : !fir.ref<i32> 63!CHECK: %[[I_VAL:.*]] = fir.load %[[I]]#0 : !fir.ref<i32> 64!CHECK: hlfir.assign %[[I_VAL]] to %[[I2]]#0 : i32, !fir.ref<i32> 65!CHECK: } 66!CHECK: omp.yield 67!CHECK: } 68!CHECK: } 69subroutine lastprivate_iv_dec() 70 integer :: i 71 72 !$omp do lastprivate(i) 73 do i = 10, 1, -3 74 end do 75 !$omp end do 76end subroutine 77 78 79!CHECK-LABEL: @_QPlastprivate_iv_i1 80subroutine lastprivate_iv_i1 81 integer*1 :: i1 82 i1=0 83!CHECK: omp.wsloop 84!CHECK: omp.loop_nest 85!CHECK: fir.if %{{.*}} { 86!CHECK: %[[I8_VAL:.*]] = fir.convert %{{.*}} : (i32) -> i8 87!CHECK: fir.store %[[I8_VAL]] to %[[IV:.*]]#1 : !fir.ref<i8> 88!CHECK: %[[IV_VAL:.*]] = fir.load %[[IV]]#0 : !fir.ref<i8> 89!CHECK: hlfir.assign %[[IV_VAL]] to %{{.*}}#0 : i8, !fir.ref<i8> 90!CHECK: } 91 !$omp do lastprivate(i1) 92 do i1=1,8 93 enddo 94!$omp end do 95end subroutine 96