xref: /llvm-project/flang/test/Lower/OpenMP/wsloop-collapse.f90 (revision 937cbce14c9aa956342a9c818c26a8a557802843)
15b66987cSKiran Chandramohan! This test checks lowering of OpenMP DO Directive(Worksharing) with collapse.
25b66987cSKiran Chandramohan
35b66987cSKiran Chandramohan! RUN: bbc -fopenmp -emit-hlfir %s -o - | FileCheck %s
45b66987cSKiran Chandramohan
55b66987cSKiran Chandramohan!CHECK-LABEL:   func.func @_QQmain() attributes {fir.bindc_name = "wsloop_collapse"} {
65b66987cSKiran Chandramohanprogram wsloop_collapse
75b66987cSKiran Chandramohan!CHECK:           %[[VAL_6:.*]] = fir.alloca i32 {bindc_name = "a", uniq_name = "_QFEa"}
85b66987cSKiran Chandramohan!CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_6]] {uniq_name = "_QFEa"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
96af4118fSKareem Ergawy
105b66987cSKiran Chandramohan!CHECK:           %[[VAL_8:.*]] = fir.alloca i32 {bindc_name = "b", uniq_name = "_QFEb"}
115b66987cSKiran Chandramohan!CHECK:           %[[VAL_9:.*]]:2 = hlfir.declare %[[VAL_8]] {uniq_name = "_QFEb"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
126af4118fSKareem Ergawy
135b66987cSKiran Chandramohan!CHECK:           %[[VAL_10:.*]] = fir.alloca i32 {bindc_name = "c", uniq_name = "_QFEc"}
145b66987cSKiran Chandramohan!CHECK:           %[[VAL_11:.*]]:2 = hlfir.declare %[[VAL_10]] {uniq_name = "_QFEc"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
156af4118fSKareem Ergawy
166af4118fSKareem Ergawy
175b66987cSKiran Chandramohan!CHECK:           %[[VAL_12:.*]] = fir.alloca i32 {bindc_name = "i", uniq_name = "_QFEi"}
185b66987cSKiran Chandramohan!CHECK:           %[[VAL_13:.*]]:2 = hlfir.declare %[[VAL_12]] {uniq_name = "_QFEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
196af4118fSKareem Ergawy
205b66987cSKiran Chandramohan!CHECK:           %[[VAL_14:.*]] = fir.alloca i32 {bindc_name = "j", uniq_name = "_QFEj"}
215b66987cSKiran Chandramohan!CHECK:           %[[VAL_15:.*]]:2 = hlfir.declare %[[VAL_14]] {uniq_name = "_QFEj"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
226af4118fSKareem Ergawy
235b66987cSKiran Chandramohan!CHECK:           %[[VAL_16:.*]] = fir.alloca i32 {bindc_name = "k", uniq_name = "_QFEk"}
245b66987cSKiran Chandramohan!CHECK:           %[[VAL_17:.*]]:2 = hlfir.declare %[[VAL_16]] {uniq_name = "_QFEk"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
256af4118fSKareem Ergawy
265b66987cSKiran Chandramohan!CHECK:           %[[VAL_18:.*]] = fir.alloca i32 {bindc_name = "x", uniq_name = "_QFEx"}
275b66987cSKiran Chandramohan!CHECK:           %[[VAL_19:.*]]:2 = hlfir.declare %[[VAL_18]] {uniq_name = "_QFEx"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
286af4118fSKareem Ergawy
296af4118fSKareem Ergawy!CHECK:           %[[VAL_20:.*]] = arith.constant 3 : i32
306af4118fSKareem Ergawy!CHECK:           hlfir.assign %[[VAL_20]] to %[[VAL_7]]#0 : i32, !fir.ref<i32>
316af4118fSKareem Ergawy
326af4118fSKareem Ergawy!CHECK:           %[[VAL_21:.*]] = arith.constant 2 : i32
336af4118fSKareem Ergawy!CHECK:           hlfir.assign %[[VAL_21]] to %[[VAL_9]]#0 : i32, !fir.ref<i32>
346af4118fSKareem Ergawy
356af4118fSKareem Ergawy!CHECK:           %[[VAL_22:.*]] = arith.constant 5 : i32
366af4118fSKareem Ergawy!CHECK:           hlfir.assign %[[VAL_22]] to %[[VAL_11]]#0 : i32, !fir.ref<i32>
376af4118fSKareem Ergawy
386af4118fSKareem Ergawy!CHECK:           %[[VAL_23:.*]] = arith.constant 0 : i32
396af4118fSKareem Ergawy!CHECK:           hlfir.assign %[[VAL_23]] to %[[VAL_19]]#0 : i32, !fir.ref<i32>
406af4118fSKareem Ergawy
41*937cbce1SKareem Ergawy!CHECK:           %[[VAL_4:.*]] = fir.alloca i32 {bindc_name = "i", pinned, {{.*}}}
42*937cbce1SKareem Ergawy!CHECK:           %[[VAL_5:.*]]:2 = hlfir.declare %[[VAL_4]] {uniq_name = "_QFEi"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
43*937cbce1SKareem Ergawy
44*937cbce1SKareem Ergawy!CHECK:           %[[VAL_2:.*]] = fir.alloca i32 {bindc_name = "j", pinned, {{.*}}}
45*937cbce1SKareem Ergawy!CHECK:           %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_2]] {uniq_name = "_QFEj"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
46*937cbce1SKareem Ergawy
47*937cbce1SKareem Ergawy!CHECK:           %[[VAL_0:.*]] = fir.alloca i32 {bindc_name = "k", pinned, {{.*}}}
48*937cbce1SKareem Ergawy!CHECK:           %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] {uniq_name = "_QFEk"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
49*937cbce1SKareem Ergawy
505b66987cSKiran Chandramohan  integer :: i, j, k
515b66987cSKiran Chandramohan  integer :: a, b, c
525b66987cSKiran Chandramohan  integer :: x
536af4118fSKareem Ergawy
545b66987cSKiran Chandramohan  a=3
555b66987cSKiran Chandramohan  b=2
565b66987cSKiran Chandramohan  c=5
575b66987cSKiran Chandramohan  x=0
585b66987cSKiran Chandramohan
595b66987cSKiran Chandramohan!CHECK:           %[[VAL_24:.*]] = arith.constant 1 : i32
605b66987cSKiran Chandramohan!CHECK:           %[[VAL_25:.*]] = fir.load %[[VAL_7]]#0 : !fir.ref<i32>
615b66987cSKiran Chandramohan!CHECK:           %[[VAL_26:.*]] = arith.constant 1 : i32
625b66987cSKiran Chandramohan!CHECK:           %[[VAL_27:.*]] = arith.constant 1 : i32
635b66987cSKiran Chandramohan!CHECK:           %[[VAL_28:.*]] = fir.load %[[VAL_9]]#0 : !fir.ref<i32>
645b66987cSKiran Chandramohan!CHECK:           %[[VAL_29:.*]] = arith.constant 1 : i32
655b66987cSKiran Chandramohan!CHECK:           %[[VAL_30:.*]] = arith.constant 1 : i32
665b66987cSKiran Chandramohan!CHECK:           %[[VAL_31:.*]] = fir.load %[[VAL_11]]#0 : !fir.ref<i32>
675b66987cSKiran Chandramohan!CHECK:           %[[VAL_32:.*]] = arith.constant 1 : i32
68*937cbce1SKareem Ergawy!CHECK:           omp.wsloop {
69ca4dbc27SSergio Afonso!CHECK-NEXT:        omp.loop_nest (%[[VAL_33:.*]], %[[VAL_34:.*]], %[[VAL_35:.*]]) : i32 = (%[[VAL_24]], %[[VAL_27]], %[[VAL_30]]) to (%[[VAL_25]], %[[VAL_28]], %[[VAL_31]]) inclusive step (%[[VAL_26]], %[[VAL_29]], %[[VAL_32]]) {
705b66987cSKiran Chandramohan  !$omp do collapse(3)
715b66987cSKiran Chandramohan  do i = 1, a
725b66987cSKiran Chandramohan     do j= 1, b
735b66987cSKiran Chandramohan        do k = 1, c
745b66987cSKiran Chandramohan!CHECK:               fir.store %[[VAL_33]] to %[[VAL_5]]#1 : !fir.ref<i32>
755b66987cSKiran Chandramohan!CHECK:               fir.store %[[VAL_34]] to %[[VAL_3]]#1 : !fir.ref<i32>
765b66987cSKiran Chandramohan!CHECK:               fir.store %[[VAL_35]] to %[[VAL_1]]#1 : !fir.ref<i32>
775b66987cSKiran Chandramohan!CHECK:               %[[VAL_36:.*]] = fir.load %[[VAL_19]]#0 : !fir.ref<i32>
785b66987cSKiran Chandramohan!CHECK:               %[[VAL_37:.*]] = fir.load %[[VAL_5]]#0 : !fir.ref<i32>
795b66987cSKiran Chandramohan!CHECK:               %[[VAL_38:.*]] = arith.addi %[[VAL_36]], %[[VAL_37]] : i32
805b66987cSKiran Chandramohan!CHECK:               %[[VAL_39:.*]] = fir.load %[[VAL_3]]#0 : !fir.ref<i32>
815b66987cSKiran Chandramohan!CHECK:               %[[VAL_40:.*]] = arith.addi %[[VAL_38]], %[[VAL_39]] : i32
825b66987cSKiran Chandramohan!CHECK:               %[[VAL_41:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<i32>
835b66987cSKiran Chandramohan!CHECK:               %[[VAL_42:.*]] = arith.addi %[[VAL_40]], %[[VAL_41]] : i32
845b66987cSKiran Chandramohan!CHECK:               hlfir.assign %[[VAL_42]] to %[[VAL_19]]#0 : i32, !fir.ref<i32>
855b66987cSKiran Chandramohan!CHECK:               omp.yield
86ca4dbc27SSergio Afonso!CHECK-NEXT:        }
875b66987cSKiran Chandramohan           x = x + i + j + k
885b66987cSKiran Chandramohan        end do
895b66987cSKiran Chandramohan     end do
905b66987cSKiran Chandramohan  end do
915b66987cSKiran Chandramohan!CHECK:           }
925b66987cSKiran Chandramohan  !$omp end do
935b66987cSKiran Chandramohan!CHECK:         return
945b66987cSKiran Chandramohan!CHECK:       }
955b66987cSKiran Chandramohanend program wsloop_collapse
96