xref: /llvm-project/flang/test/Lower/OpenMP/wsloop-variable.f90 (revision 937cbce14c9aa956342a9c818c26a8a557802843)
15b66987cSKiran Chandramohan! This test checks lowering of OpenMP DO Directive(Worksharing) for different
25b66987cSKiran Chandramohan! types of loop iteration variable, lower bound, upper bound, and step.
35b66987cSKiran Chandramohan
45b66987cSKiran Chandramohan!REQUIRES: shell
55b66987cSKiran Chandramohan!RUN: bbc -fopenmp -emit-hlfir %s -o - 2>&1 | FileCheck %s
65b66987cSKiran Chandramohan
75b66987cSKiran Chandramohan!CHECK:  OpenMP loop iteration variable cannot have more than 64 bits size and will be narrowed into 64 bits.
85b66987cSKiran Chandramohan
95b66987cSKiran Chandramohanprogram wsloop_variable
105b66987cSKiran Chandramohan  integer(kind=1) :: i1_lb, i1_ub
115b66987cSKiran Chandramohan  integer(kind=2) :: i2, i2_ub, i2_s
125b66987cSKiran Chandramohan  integer(kind=4) :: i4_s
135b66987cSKiran Chandramohan  integer(kind=8) :: i8, i8_s
145b66987cSKiran Chandramohan  integer(kind=16) :: i16, i16_lb
155b66987cSKiran Chandramohan  real :: x
165b66987cSKiran Chandramohan
175b66987cSKiran Chandramohan!CHECK:      %[[TMP0:.*]] = arith.constant 1 : i32
185b66987cSKiran Chandramohan!CHECK:      %[[TMP1:.*]] = arith.constant 100 : i32
195b66987cSKiran Chandramohan!CHECK:      %[[TMP2:.*]] = fir.convert %[[TMP0]] : (i32) -> i64
205b66987cSKiran Chandramohan!CHECK:      %[[TMP3:.*]] = fir.convert %{{.*}} : (i8) -> i64
215b66987cSKiran Chandramohan!CHECK:      %[[TMP4:.*]] = fir.convert %{{.*}} : (i16) -> i64
225b66987cSKiran Chandramohan!CHECK:      %[[TMP5:.*]] = fir.convert %{{.*}} : (i128) -> i64
235b66987cSKiran Chandramohan!CHECK:      %[[TMP6:.*]] = fir.convert %[[TMP1]] : (i32) -> i64
245b66987cSKiran Chandramohan!CHECK:      %[[TMP7:.*]] = fir.convert %{{.*}} : (i32) -> i64
25*937cbce1SKareem Ergawy!CHECK:      omp.wsloop {
26ca4dbc27SSergio Afonso!CHECK-NEXT:   omp.loop_nest (%[[ARG0:.*]], %[[ARG1:.*]]) : i64 = (%[[TMP2]], %[[TMP5]]) to (%[[TMP3]], %[[TMP6]]) inclusive step (%[[TMP4]], %[[TMP7]]) {
275b66987cSKiran Chandramohan!CHECK:          %[[ARG0_I16:.*]] = fir.convert %[[ARG0]] : (i64) -> i16
285b66987cSKiran Chandramohan!CHECK:          fir.store %[[ARG0_I16]] to %[[STORE_IV0:.*]]#1 : !fir.ref<i16>
295b66987cSKiran Chandramohan!CHECK:          fir.store %[[ARG1]] to %[[STORE_IV1:.*]]#1 : !fir.ref<i64>
305b66987cSKiran Chandramohan!CHECK:          %[[LOAD_IV0:.*]] = fir.load %[[STORE_IV0]]#0 : !fir.ref<i16>
315b66987cSKiran Chandramohan!CHECK:          %[[LOAD_IV0_I64:.*]] = fir.convert %[[LOAD_IV0]] : (i16) -> i64
325b66987cSKiran Chandramohan!CHECK:          %[[LOAD_IV1:.*]] = fir.load %[[STORE_IV1]]#0 : !fir.ref<i64>
335b66987cSKiran Chandramohan!CHECK:          %[[TMP10:.*]] = arith.addi %[[LOAD_IV0_I64]], %[[LOAD_IV1]] : i64
345b66987cSKiran Chandramohan!CHECK:          %[[TMP11:.*]] = fir.convert %[[TMP10]] : (i64) -> f32
355b66987cSKiran Chandramohan!CHECK:          hlfir.assign %[[TMP11]] to %{{.*}} : f32, !fir.ref<f32>
365b66987cSKiran Chandramohan!CHECK:          omp.yield
375b66987cSKiran Chandramohan!CHECK:        }
38ca4dbc27SSergio Afonso!CHECK:      }
395b66987cSKiran Chandramohan
405b66987cSKiran Chandramohan  !$omp do collapse(2)
415b66987cSKiran Chandramohan  do i2 = 1, i1_ub, i2_s
425b66987cSKiran Chandramohan    do i8 = i16_lb, 100, i4_s
435b66987cSKiran Chandramohan      x = i2 + i8
445b66987cSKiran Chandramohan    end do
455b66987cSKiran Chandramohan  end do
465b66987cSKiran Chandramohan  !$omp end do
475b66987cSKiran Chandramohan
485b66987cSKiran Chandramohan!CHECK:      %[[TMP12:.*]] = arith.constant 1 : i32
495b66987cSKiran Chandramohan!CHECK:      %[[TMP13:.*]] = fir.convert %{{.*}} : (i8) -> i32
505b66987cSKiran Chandramohan!CHECK:      %[[TMP14:.*]] = fir.convert %{{.*}} : (i64) -> i32
51*937cbce1SKareem Ergawy!CHECK:      omp.wsloop {
52ca4dbc27SSergio Afonso!CHECK-NEXT:   omp.loop_nest (%[[ARG0:.*]]) : i32 = (%[[TMP12]]) to (%[[TMP13]]) inclusive step (%[[TMP14]]) {
535b66987cSKiran Chandramohan!CHECK:          %[[ARG0_I16:.*]] = fir.convert %[[ARG0]] : (i32) -> i16
545b66987cSKiran Chandramohan!CHECK:          fir.store %[[ARG0_I16]] to %[[STORE3:.*]]#1 : !fir.ref<i16>
555b66987cSKiran Chandramohan!CHECK:          %[[LOAD3:.*]] = fir.load %[[STORE3]]#0 : !fir.ref<i16>
565b66987cSKiran Chandramohan!CHECK:          %[[TMP16:.*]] = fir.convert %[[LOAD3]] : (i16) -> f32
575b66987cSKiran Chandramohan!CHECK:          hlfir.assign %[[TMP16]] to %{{.*}} : f32, !fir.ref<f32>
585b66987cSKiran Chandramohan!CHECK:          omp.yield
595b66987cSKiran Chandramohan!CHECK:        }
60ca4dbc27SSergio Afonso!CHECK:      }
615b66987cSKiran Chandramohan
625b66987cSKiran Chandramohan  !$omp do
635b66987cSKiran Chandramohan  do i2 = 1, i1_ub, i8_s
645b66987cSKiran Chandramohan    x = i2
655b66987cSKiran Chandramohan  end do
665b66987cSKiran Chandramohan  !$omp end do
675b66987cSKiran Chandramohan
685b66987cSKiran Chandramohan!CHECK:      %[[TMP17:.*]] = fir.convert %{{.*}} : (i8) -> i64
695b66987cSKiran Chandramohan!CHECK:      %[[TMP18:.*]] = fir.convert %{{.*}} : (i16) -> i64
705b66987cSKiran Chandramohan!CHECK:      %[[TMP19:.*]] = fir.convert %{{.*}} : (i32) -> i64
71*937cbce1SKareem Ergawy!CHECK:      omp.wsloop {
72ca4dbc27SSergio Afonso!CHECK-NEXT:   omp.loop_nest (%[[ARG1:.*]]) : i64 = (%[[TMP17]]) to (%[[TMP18]]) inclusive step (%[[TMP19]])  {
735b66987cSKiran Chandramohan!CHECK:          %[[ARG1_I128:.*]] = fir.convert %[[ARG1]] : (i64) -> i128
745b66987cSKiran Chandramohan!CHECK:          fir.store %[[ARG1_I128]] to %[[STORE4:.*]]#1 : !fir.ref<i128>
755b66987cSKiran Chandramohan!CHECK:          %[[LOAD4:.*]] = fir.load %[[STORE4]]#0 : !fir.ref<i128>
765b66987cSKiran Chandramohan!CHECK:          %[[TMP21:.*]] = fir.convert %[[LOAD4]] : (i128) -> f32
775b66987cSKiran Chandramohan!CHECK:          hlfir.assign %[[TMP21]] to %{{.*}} : f32, !fir.ref<f32>
785b66987cSKiran Chandramohan!CHECK:          omp.yield
795b66987cSKiran Chandramohan!CHECK:        }
80ca4dbc27SSergio Afonso!CHECK:      }
815b66987cSKiran Chandramohan
825b66987cSKiran Chandramohan  !$omp do
835b66987cSKiran Chandramohan  do i16 = i1_lb, i2_ub, i4_s
845b66987cSKiran Chandramohan    x = i16
855b66987cSKiran Chandramohan  end do
865b66987cSKiran Chandramohan  !$omp end do
875b66987cSKiran Chandramohan
885b66987cSKiran Chandramohanend program wsloop_variable
895b66987cSKiran Chandramohan
905b66987cSKiran Chandramohan!CHECK-LABEL: func.func @_QPwsloop_variable_sub() {
915b66987cSKiran Chandramohan!CHECK:           %[[VAL_4:.*]] = fir.alloca i8 {bindc_name = "i1", uniq_name = "_QFwsloop_variable_subEi1"}
925b66987cSKiran Chandramohan!CHECK:           %[[VAL_5:.*]]:2 = hlfir.declare %[[VAL_4]] {uniq_name = "_QFwsloop_variable_subEi1"} : (!fir.ref<i8>) -> (!fir.ref<i8>, !fir.ref<i8>)
936af4118fSKareem Ergawy
945b66987cSKiran Chandramohan!CHECK:           %[[VAL_6:.*]] = fir.alloca i128 {bindc_name = "i16_lb", uniq_name = "_QFwsloop_variable_subEi16_lb"}
955b66987cSKiran Chandramohan!CHECK:           %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_6]] {uniq_name = "_QFwsloop_variable_subEi16_lb"} : (!fir.ref<i128>) -> (!fir.ref<i128>, !fir.ref<i128>)
966af4118fSKareem Ergawy
975b66987cSKiran Chandramohan!CHECK:           %[[VAL_8:.*]] = fir.alloca i8 {bindc_name = "i1_ub", uniq_name = "_QFwsloop_variable_subEi1_ub"}
985b66987cSKiran Chandramohan!CHECK:           %[[VAL_9:.*]]:2 = hlfir.declare %[[VAL_8]] {uniq_name = "_QFwsloop_variable_subEi1_ub"} : (!fir.ref<i8>) -> (!fir.ref<i8>, !fir.ref<i8>)
996af4118fSKareem Ergawy
1005b66987cSKiran Chandramohan!CHECK:           %[[VAL_10:.*]] = fir.alloca i16 {bindc_name = "i2", uniq_name = "_QFwsloop_variable_subEi2"}
1015b66987cSKiran Chandramohan!CHECK:           %[[VAL_11:.*]]:2 = hlfir.declare %[[VAL_10]] {uniq_name = "_QFwsloop_variable_subEi2"} : (!fir.ref<i16>) -> (!fir.ref<i16>, !fir.ref<i16>)
1026af4118fSKareem Ergawy
1035b66987cSKiran Chandramohan!CHECK:           %[[VAL_12:.*]] = fir.alloca i16 {bindc_name = "i2_s", uniq_name = "_QFwsloop_variable_subEi2_s"}
1045b66987cSKiran Chandramohan!CHECK:           %[[VAL_13:.*]]:2 = hlfir.declare %[[VAL_12]] {uniq_name = "_QFwsloop_variable_subEi2_s"} : (!fir.ref<i16>) -> (!fir.ref<i16>, !fir.ref<i16>)
1056af4118fSKareem Ergawy
1065b66987cSKiran Chandramohan!CHECK:           %[[VAL_14:.*]] = fir.alloca i32 {bindc_name = "i4_s", uniq_name = "_QFwsloop_variable_subEi4_s"}
1075b66987cSKiran Chandramohan!CHECK:           %[[VAL_15:.*]]:2 = hlfir.declare %[[VAL_14]] {uniq_name = "_QFwsloop_variable_subEi4_s"} : (!fir.ref<i32>) -> (!fir.ref<i32>, !fir.ref<i32>)
1086af4118fSKareem Ergawy
1095b66987cSKiran Chandramohan!CHECK:           %[[VAL_16:.*]] = fir.alloca i64 {bindc_name = "i8", uniq_name = "_QFwsloop_variable_subEi8"}
1105b66987cSKiran Chandramohan!CHECK:           %[[VAL_17:.*]]:2 = hlfir.declare %[[VAL_16]] {uniq_name = "_QFwsloop_variable_subEi8"} : (!fir.ref<i64>) -> (!fir.ref<i64>, !fir.ref<i64>)
1116af4118fSKareem Ergawy
1125b66987cSKiran Chandramohan!CHECK:           %[[VAL_18:.*]] = fir.alloca i8 {bindc_name = "j1", uniq_name = "_QFwsloop_variable_subEj1"}
1135b66987cSKiran Chandramohan!CHECK:           %[[VAL_19:.*]]:2 = hlfir.declare %[[VAL_18]] {uniq_name = "_QFwsloop_variable_subEj1"} : (!fir.ref<i8>) -> (!fir.ref<i8>, !fir.ref<i8>)
1146af4118fSKareem Ergawy
1155b66987cSKiran Chandramohan!CHECK:           %[[VAL_20:.*]] = fir.alloca f32 {bindc_name = "x", uniq_name = "_QFwsloop_variable_subEx"}
1165b66987cSKiran Chandramohan!CHECK:           %[[VAL_21:.*]]:2 = hlfir.declare %[[VAL_20]] {uniq_name = "_QFwsloop_variable_subEx"} : (!fir.ref<f32>) -> (!fir.ref<f32>, !fir.ref<f32>)
1175b66987cSKiran Chandramohan
1185b66987cSKiran Chandramohansubroutine wsloop_variable_sub
1195b66987cSKiran Chandramohan  integer(kind=1) :: i1, i1_ub, j1
1205b66987cSKiran Chandramohan  integer(kind=2) :: i2, i2_s
1215b66987cSKiran Chandramohan  integer(kind=4) :: i4_s
1225b66987cSKiran Chandramohan  integer(kind=8) :: i8
1235b66987cSKiran Chandramohan  integer(kind=16) :: i16_lb
1245b66987cSKiran Chandramohan  real :: x
1255b66987cSKiran Chandramohan
126*937cbce1SKareem Ergawy!CHECK:           %[[VAL_2:.*]] = fir.alloca i16 {bindc_name = "i2", pinned, {{.*}}}
127*937cbce1SKareem Ergawy!CHECK:           %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_2]] {uniq_name = "_QFwsloop_variable_subEi2"} : (!fir.ref<i16>) -> (!fir.ref<i16>, !fir.ref<i16>)
128*937cbce1SKareem Ergawy
1295b66987cSKiran Chandramohan!CHECK:           %[[VAL_22:.*]] = arith.constant 1 : i32
1305b66987cSKiran Chandramohan!CHECK:           %[[VAL_23:.*]] = fir.load %[[VAL_9]]#0 : !fir.ref<i8>
1315b66987cSKiran Chandramohan!CHECK:           %[[VAL_24:.*]] = fir.load %[[VAL_13]]#0 : !fir.ref<i16>
1325b66987cSKiran Chandramohan!CHECK:           %[[VAL_25:.*]] = fir.convert %[[VAL_23]] : (i8) -> i32
1335b66987cSKiran Chandramohan!CHECK:           %[[VAL_26:.*]] = fir.convert %[[VAL_24]] : (i16) -> i32
134*937cbce1SKareem Ergawy!CHECK:           omp.wsloop {
135ca4dbc27SSergio Afonso!CHECK-NEXT:        omp.loop_nest (%[[VAL_27:.*]]) : i32 = (%[[VAL_22]]) to (%[[VAL_25]]) inclusive step (%[[VAL_26]]) {
1365b66987cSKiran Chandramohan!CHECK:               %[[VAL_28:.*]] = fir.convert %[[VAL_27]] : (i32) -> i16
1375b66987cSKiran Chandramohan!CHECK:               fir.store %[[VAL_28]] to %[[VAL_3]]#1 : !fir.ref<i16>
1385b66987cSKiran Chandramohan!CHECK:               %[[VAL_29:.*]] = fir.load %[[VAL_7]]#0 : !fir.ref<i128>
1395b66987cSKiran Chandramohan!CHECK:               %[[VAL_30:.*]] = fir.convert %[[VAL_29]] : (i128) -> index
1405b66987cSKiran Chandramohan!CHECK:               %[[VAL_31:.*]] = arith.constant 100 : i32
1415b66987cSKiran Chandramohan!CHECK:               %[[VAL_32:.*]] = fir.convert %[[VAL_31]] : (i32) -> index
1425b66987cSKiran Chandramohan!CHECK:               %[[VAL_33:.*]] = fir.load %[[VAL_15]]#0 : !fir.ref<i32>
1435b66987cSKiran Chandramohan!CHECK:               %[[VAL_34:.*]] = fir.convert %[[VAL_33]] : (i32) -> index
1445b66987cSKiran Chandramohan!CHECK:               %[[VAL_35:.*]] = fir.convert %[[VAL_30]] : (index) -> i64
1455b66987cSKiran Chandramohan!CHECK:               %[[VAL_36:.*]]:2 = fir.do_loop %[[VAL_37:.*]] = %[[VAL_30]] to %[[VAL_32]] step %[[VAL_34]] iter_args(%[[VAL_38:.*]] = %[[VAL_35]]) -> (index, i64) {
1465b66987cSKiran Chandramohan!CHECK:                 fir.store %[[VAL_38]] to %[[VAL_17]]#1 : !fir.ref<i64>
1475b66987cSKiran Chandramohan!CHECK:                 %[[VAL_39:.*]] = fir.load %[[VAL_3]]#0 : !fir.ref<i16>
1485b66987cSKiran Chandramohan!CHECK:                 %[[VAL_40:.*]] = fir.convert %[[VAL_39]] : (i16) -> i64
1495b66987cSKiran Chandramohan!CHECK:                 %[[VAL_41:.*]] = fir.load %[[VAL_17]]#0 : !fir.ref<i64>
1505b66987cSKiran Chandramohan!CHECK:                 %[[VAL_42:.*]] = arith.addi %[[VAL_40]], %[[VAL_41]] : i64
1515b66987cSKiran Chandramohan!CHECK:                 %[[VAL_43:.*]] = fir.convert %[[VAL_42]] : (i64) -> f32
1525b66987cSKiran Chandramohan!CHECK:                 hlfir.assign %[[VAL_43]] to %[[VAL_21]]#0 : f32, !fir.ref<f32>
153a88677edSYusuke MINATO!CHECK:                 %[[VAL_44:.*]] = arith.addi %[[VAL_37]], %[[VAL_34]] overflow<nsw> : index
1545b66987cSKiran Chandramohan!CHECK:                 %[[VAL_45:.*]] = fir.convert %[[VAL_34]] : (index) -> i64
1555b66987cSKiran Chandramohan!CHECK:                 %[[VAL_46:.*]] = fir.load %[[VAL_17]]#1 : !fir.ref<i64>
156a88677edSYusuke MINATO!CHECK:                 %[[VAL_47:.*]] = arith.addi %[[VAL_46]], %[[VAL_45]] overflow<nsw> : i64
1575b66987cSKiran Chandramohan!CHECK:                 fir.result %[[VAL_44]], %[[VAL_47]] : index, i64
1585b66987cSKiran Chandramohan!CHECK:               }
1595b66987cSKiran Chandramohan!CHECK:               fir.store %[[VAL_48:.*]]#1 to %[[VAL_17]]#1 : !fir.ref<i64>
1605b66987cSKiran Chandramohan!CHECK:               omp.yield
1615b66987cSKiran Chandramohan!CHECK:             }
162ca4dbc27SSergio Afonso!CHECK:           }
1635b66987cSKiran Chandramohan
1645b66987cSKiran Chandramohan  !$omp do
1655b66987cSKiran Chandramohan  do i2 = 1, i1_ub, i2_s
1665b66987cSKiran Chandramohan    do i8 = i16_lb, 100, i4_s
1675b66987cSKiran Chandramohan      x = i2 + i8
1685b66987cSKiran Chandramohan    end do
1695b66987cSKiran Chandramohan  end do
1705b66987cSKiran Chandramohan  !$omp end do
1715b66987cSKiran Chandramohan
1725b66987cSKiran Chandramohan!CHECK:           %[[VAL_49:.*]] = arith.constant 5 : i8
1735b66987cSKiran Chandramohan!CHECK:           hlfir.assign %[[VAL_49]] to %[[VAL_19]]#0 : i8, !fir.ref<i8>
1746af4118fSKareem Ergawy
175*937cbce1SKareem Ergawy!CHECK:           %[[VAL_0:.*]] = fir.alloca i8 {bindc_name = "i1", pinned, {{.*}}}
176*937cbce1SKareem Ergawy!CHECK:           %[[VAL_1:.*]]:2 = hlfir.declare %[[VAL_0]] {uniq_name = "_QFwsloop_variable_subEi1"} : (!fir.ref<i8>) -> (!fir.ref<i8>, !fir.ref<i8>)
1776af4118fSKareem Ergawy
1785b66987cSKiran Chandramohan!CHECK:           %[[VAL_50:.*]] = arith.constant 1 : i32
1795b66987cSKiran Chandramohan!CHECK:           %[[VAL_51:.*]] = arith.constant 10 : i32
1805b66987cSKiran Chandramohan!CHECK:           %[[VAL_52:.*]] = arith.constant 1 : i32
181*937cbce1SKareem Ergawy!CHECK:           omp.wsloop {
182ca4dbc27SSergio Afonso!CHECK-NEXT:        omp.loop_nest (%[[VAL_53:.*]]) : i32 = (%[[VAL_50]]) to (%[[VAL_51]]) inclusive step (%[[VAL_52]]) {
1835b66987cSKiran Chandramohan!CHECK:               %[[VAL_54:.*]] = fir.convert %[[VAL_53]] : (i32) -> i8
1845b66987cSKiran Chandramohan!CHECK:               fir.store %[[VAL_54]] to %[[VAL_1]]#1 : !fir.ref<i8>
1855b66987cSKiran Chandramohan!CHECK:               %[[VAL_55:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<i8>
1865b66987cSKiran Chandramohan!CHECK:               %[[VAL_56:.*]] = fir.load %[[VAL_19]]#0 : !fir.ref<i8>
1875b66987cSKiran Chandramohan!CHECK:               %[[VAL_57:.*]] = arith.cmpi eq, %[[VAL_55]], %[[VAL_56]] : i8
1885b66987cSKiran Chandramohan!CHECK:               fir.if %[[VAL_57]] {
1895b66987cSKiran Chandramohan!CHECK:               }
1905b66987cSKiran Chandramohan!CHECK:               omp.yield
1915b66987cSKiran Chandramohan!CHECK:             }
192ca4dbc27SSergio Afonso!CHECK:           }
1935b66987cSKiran Chandramohan  j1 = 5
1945b66987cSKiran Chandramohan  !$omp do
1955b66987cSKiran Chandramohan  do i1 = 1, 10
1965b66987cSKiran Chandramohan    if (i1 .eq. j1) then
1975b66987cSKiran Chandramohan      print *, "EQ"
1985b66987cSKiran Chandramohan    end if
1995b66987cSKiran Chandramohan  end do
2005b66987cSKiran Chandramohan  !$omp end do
2015b66987cSKiran Chandramohan
2025b66987cSKiran Chandramohan!CHECK:         return
2035b66987cSKiran Chandramohan!CHECK:       }
2045b66987cSKiran Chandramohan
2055b66987cSKiran Chandramohanend
206