1! Test lowering of user defined elemental procedure reference to HLFIR 2! RUN: bbc -emit-hlfir -o - %s 2>&1 | FileCheck %s 3 4subroutine by_addr(x, y) 5 integer :: x 6 real :: y(100) 7 interface 8 real elemental function elem(a, b) 9 integer, intent(in) :: a 10 real, intent(in) :: b 11 end function 12 end interface 13 call baz(elem(x, y)) 14end subroutine 15! CHECK-LABEL: func.func @_QPby_addr( 16! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0:.*]] {{.*}}x 17! CHECK: %[[VAL_5:.*]]:2 = hlfir.declare %[[VAL_1:.*]](%[[VAL_4:[^)]*]]) {{.*}}y 18! CHECK: %[[VAL_6:.*]] = hlfir.elemental %[[VAL_4]] unordered : (!fir.shape<1>) -> !hlfir.expr<100xf32> { 19! CHECK: ^bb0(%[[VAL_7:.*]]: index): 20! CHECK: %[[VAL_8:.*]] = hlfir.designate %[[VAL_5]]#0 (%[[VAL_7]]) : (!fir.ref<!fir.array<100xf32>>, index) -> !fir.ref<f32> 21! CHECK: %[[VAL_9:.*]] = fir.call @_QPelem(%[[VAL_2]]#1, %[[VAL_8]]) proc_attrs<elemental, pure> fastmath<contract> : (!fir.ref<i32>, !fir.ref<f32>) -> f32 22! CHECK: hlfir.yield_element %[[VAL_9]] : f32 23! CHECK: } 24! CHECK: fir.call 25! CHECK: hlfir.destroy %[[VAL_6]] 26 27subroutine by_value(x, y) 28 integer :: x 29 real :: y(10, 20) 30 interface 31 real elemental function elem_val(a, b) 32 integer, value :: a 33 real, value :: b 34 end function 35 end interface 36 call baz(elem_val(x, y)) 37end subroutine 38! CHECK-LABEL: func.func @_QPby_value( 39! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0:.*]] {{.*}}x 40! CHECK: %[[VAL_6:.*]]:2 = hlfir.declare %[[VAL_1:.*]](%[[VAL_5:[^)]*]]) {{.*}}y 41! CHECK: %[[VAL_7:.*]] = fir.load %[[VAL_2]]#0 : !fir.ref<i32> 42! CHECK: %[[VAL_8:.*]] = hlfir.elemental %[[VAL_5]] unordered : (!fir.shape<2>) -> !hlfir.expr<10x20xf32> { 43! CHECK: ^bb0(%[[VAL_9:.*]]: index, %[[VAL_10:.*]]: index): 44! CHECK: %[[VAL_11:.*]] = hlfir.designate %[[VAL_6]]#0 (%[[VAL_9]], %[[VAL_10]]) : (!fir.ref<!fir.array<10x20xf32>>, index, index) -> !fir.ref<f32> 45! CHECK: %[[VAL_12:.*]] = fir.load %[[VAL_11]] : !fir.ref<f32> 46! CHECK: %[[VAL_13:.*]] = fir.call @_QPelem_val(%[[VAL_7]], %[[VAL_12]]) proc_attrs<elemental, pure> fastmath<contract> : (i32, f32) -> f32 47! CHECK: hlfir.yield_element %[[VAL_13]] : f32 48! CHECK: } 49! CHECK: fir.call 50! CHECK: hlfir.destroy %[[VAL_8]] 51 52subroutine by_boxaddr(x, y) 53 character(*) :: x 54 character(*) :: y(100) 55 interface 56 real elemental function char_elem(a, b) 57 character(*), intent(in) :: a 58 character(*), intent(in) :: b 59 end function 60 end interface 61 call baz2(char_elem(x, y)) 62end subroutine 63! CHECK-LABEL: func.func @_QPby_boxaddr( 64! CHECK: %[[VAL_3:.*]]:2 = hlfir.declare %[[VAL_2:.*]]#0 typeparams %[[VAL_2]]#1 {{.*}}x 65! CHECK: %[[VAL_6:.*]] = arith.constant 100 : index 66! CHECK: %[[VAL_8:.*]]:2 = hlfir.declare %[[VAL_5:.*]](%[[VAL_7:.*]]) typeparams %[[VAL_4:.*]]#1 {{.*}}y 67! CHECK: %[[VAL_9:.*]] = hlfir.elemental %[[VAL_7]] unordered : (!fir.shape<1>) -> !hlfir.expr<100xf32> { 68! CHECK: ^bb0(%[[VAL_10:.*]]: index): 69! CHECK: %[[VAL_11:.*]] = hlfir.designate %[[VAL_8]]#0 (%[[VAL_10]]) typeparams %[[VAL_4]]#1 : (!fir.box<!fir.array<100x!fir.char<1,?>>>, index, index) -> !fir.boxchar<1> 70! CHECK: %[[VAL_12:.*]] = fir.call @_QPchar_elem(%[[VAL_3]]#0, %[[VAL_11]]) proc_attrs<elemental, pure> fastmath<contract> : (!fir.boxchar<1>, !fir.boxchar<1>) -> f32 71! CHECK: hlfir.yield_element %[[VAL_12]] : f32 72! CHECK: } 73! CHECK: fir.call 74! CHECK: hlfir.destroy %[[VAL_9]] 75 76subroutine sub(x, y) 77 integer :: x 78 real :: y(10, 20) 79 interface 80 elemental subroutine elem_sub(a, b) 81 integer, intent(in) :: a 82 real, intent(in) :: b 83 end subroutine 84 end interface 85 call elem_sub(x, y) 86end subroutine 87! CHECK-LABEL: func.func @_QPsub( 88! CHECK: %[[VAL_2:.*]]:2 = hlfir.declare %[[VAL_0:.*]] {{.*}}x 89! CHECK: %[[VAL_3:.*]] = arith.constant 10 : index 90! CHECK: %[[VAL_4:.*]] = arith.constant 20 : index 91! CHECK: %[[VAL_6:.*]]:2 = hlfir.declare %[[VAL_1:.*]](%[[VAL_5:[^)]*]]) {{.*}}y 92! CHECK: %[[VAL_7:.*]] = arith.constant 1 : index 93! CHECK: fir.do_loop %[[VAL_8:.*]] = %[[VAL_7]] to %[[VAL_4]] step %[[VAL_7]] unordered { 94! CHECK: fir.do_loop %[[VAL_9:.*]] = %[[VAL_7]] to %[[VAL_3]] step %[[VAL_7]] unordered { 95! CHECK: %[[VAL_10:.*]] = hlfir.designate %[[VAL_6]]#0 (%[[VAL_9]], %[[VAL_8]]) : (!fir.ref<!fir.array<10x20xf32>>, index, index) -> !fir.ref<f32> 96! CHECK: fir.call @_QPelem_sub(%[[VAL_2]]#1, %[[VAL_10]]) proc_attrs<elemental, pure> fastmath<contract> : (!fir.ref<i32>, !fir.ref<f32>) -> () 97! CHECK: } 98! CHECK: } 99 100subroutine impure_elemental(x) 101 real :: x(10, 20) 102 interface 103 impure elemental subroutine impure_elem(a) 104 real, intent(in) :: a 105 end subroutine 106 end interface 107 call impure_elem(x) 108end subroutine 109! CHECK-LABEL: func.func @_QPimpure_elemental( 110! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.array<10x20xf32>> {fir.bindc_name = "x"}) { 111! CHECK: %[[VAL_1:.*]] = arith.constant 10 : index 112! CHECK: %[[VAL_2:.*]] = arith.constant 20 : index 113! CHECK: %[[VAL_3:.*]] = fir.shape %[[VAL_1]], %[[VAL_2]] : (index, index) -> !fir.shape<2> 114! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %[[VAL_0]](%[[VAL_3]]) dummy_scope %{{[0-9]+}} {uniq_name = "_QFimpure_elementalEx"} : (!fir.ref<!fir.array<10x20xf32>>, !fir.shape<2>, !fir.dscope) -> (!fir.ref<!fir.array<10x20xf32>>, !fir.ref<!fir.array<10x20xf32>>) 115! CHECK: %[[VAL_5:.*]] = arith.constant 1 : index 116! CHECK: fir.do_loop %[[VAL_6:.*]] = %[[VAL_5]] to %[[VAL_2]] step %[[VAL_5]] { 117! CHECK: fir.do_loop %[[VAL_7:.*]] = %[[VAL_5]] to %[[VAL_1]] step %[[VAL_5]] { 118! CHECK: %[[VAL_8:.*]] = hlfir.designate %[[VAL_4]]#0 (%[[VAL_7]], %[[VAL_6]]) : (!fir.ref<!fir.array<10x20xf32>>, index, index) -> !fir.ref<f32> 119! CHECK: fir.call @_QPimpure_elem(%[[VAL_8]]) proc_attrs<elemental> fastmath<contract> : (!fir.ref<f32>) -> () 120! CHECK: } 121! CHECK: } 122! CHECK: return 123! CHECK: } 124 125subroutine ordered_elemental(x) 126 real :: x(10, 20) 127 interface 128 elemental subroutine ordered_elem(a) 129 real, intent(inout) :: a 130 end subroutine 131 end interface 132 call ordered_elem(x) 133end subroutine 134! CHECK-LABEL: func.func @_QPordered_elemental( 135! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.array<10x20xf32>> {fir.bindc_name = "x"}) { 136! CHECK: %[[VAL_1:.*]] = arith.constant 10 : index 137! CHECK: %[[VAL_2:.*]] = arith.constant 20 : index 138! CHECK: %[[VAL_3:.*]] = fir.shape %[[VAL_1]], %[[VAL_2]] : (index, index) -> !fir.shape<2> 139! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %[[VAL_0]](%[[VAL_3]]) dummy_scope %{{[0-9]+}} {uniq_name = "_QFordered_elementalEx"} : (!fir.ref<!fir.array<10x20xf32>>, !fir.shape<2>, !fir.dscope) -> (!fir.ref<!fir.array<10x20xf32>>, !fir.ref<!fir.array<10x20xf32>>) 140! CHECK: %[[VAL_5:.*]] = arith.constant 1 : index 141! CHECK: fir.do_loop %[[VAL_6:.*]] = %[[VAL_5]] to %[[VAL_2]] step %[[VAL_5]] { 142! CHECK: fir.do_loop %[[VAL_7:.*]] = %[[VAL_5]] to %[[VAL_1]] step %[[VAL_5]] { 143! CHECK: %[[VAL_8:.*]] = hlfir.designate %[[VAL_4]]#0 (%[[VAL_7]], %[[VAL_6]]) : (!fir.ref<!fir.array<10x20xf32>>, index, index) -> !fir.ref<f32> 144! CHECK: fir.call @_QPordered_elem(%[[VAL_8]]) proc_attrs<elemental, pure> fastmath<contract> : (!fir.ref<f32>) -> () 145! CHECK: } 146! CHECK: } 147! CHECK: return 148! CHECK: } 149 150subroutine impure_elemental_arg_eval(x) 151 real :: x(10, 20) 152 interface 153 impure elemental subroutine impure_elem(a) 154 real, intent(in) :: a 155 end subroutine 156 end interface 157 call impure_elem((x)) 158end subroutine 159! CHECK-LABEL: func.func @_QPimpure_elemental_arg_eval( 160! CHECK-SAME: %[[VAL_0:.*]]: !fir.ref<!fir.array<10x20xf32>> {fir.bindc_name = "x"}) { 161! CHECK: %[[VAL_1:.*]] = arith.constant 10 : index 162! CHECK: %[[VAL_2:.*]] = arith.constant 20 : index 163! CHECK: %[[VAL_3:.*]] = fir.shape %[[VAL_1]], %[[VAL_2]] : (index, index) -> !fir.shape<2> 164! CHECK: %[[VAL_4:.*]]:2 = hlfir.declare %[[VAL_0]](%[[VAL_3]]) dummy_scope %{{[0-9]+}} {uniq_name = "_QFimpure_elemental_arg_evalEx"} : (!fir.ref<!fir.array<10x20xf32>>, !fir.shape<2>, !fir.dscope) -> (!fir.ref<!fir.array<10x20xf32>>, !fir.ref<!fir.array<10x20xf32>>) 165! CHECK: %[[VAL_5:.*]] = hlfir.elemental %[[VAL_3]] unordered : (!fir.shape<2>) -> !hlfir.expr<10x20xf32> { 166! CHECK: ^bb0(%[[VAL_6:.*]]: index, %[[VAL_7:.*]]: index): 167! CHECK: %[[VAL_8:.*]] = hlfir.designate %[[VAL_4]]#0 (%[[VAL_6]], %[[VAL_7]]) : (!fir.ref<!fir.array<10x20xf32>>, index, index) -> !fir.ref<f32> 168! CHECK: %[[VAL_9:.*]] = fir.load %[[VAL_8]] : !fir.ref<f32> 169! CHECK: %[[VAL_10:.*]] = hlfir.no_reassoc %[[VAL_9]] : f32 170! CHECK: hlfir.yield_element %[[VAL_10]] : f32 171! CHECK: } 172! CHECK: %[[VAL_11:.*]]:3 = hlfir.associate %[[VAL_5]](%[[VAL_3]]) {uniq_name = "adapt.impure_arg_eval"} : (!hlfir.expr<10x20xf32>, !fir.shape<2>) -> (!fir.ref<!fir.array<10x20xf32>>, !fir.ref<!fir.array<10x20xf32>>, i1) 173! CHECK: %[[VAL_13:.*]] = arith.constant 1 : index 174! CHECK: fir.do_loop %[[VAL_14:.*]] = %[[VAL_13]] to %[[VAL_2]] step %[[VAL_13]] { 175! CHECK: fir.do_loop %[[VAL_15:.*]] = %[[VAL_13]] to %[[VAL_1]] step %[[VAL_13]] { 176! CHECK: %[[VAL_16:.*]] = hlfir.designate %[[VAL_11]]#0 (%[[VAL_15]], %[[VAL_14]]) : (!fir.ref<!fir.array<10x20xf32>>, index, index) -> !fir.ref<f32> 177! CHECK: fir.call @_QPimpure_elem(%[[VAL_16]]) proc_attrs<elemental> fastmath<contract> : (!fir.ref<f32>) -> () 178! CHECK: } 179! CHECK: } 180! CHECK: hlfir.end_associate %[[VAL_11]]#1, %[[VAL_11]]#2 : !fir.ref<!fir.array<10x20xf32>>, i1 181! CHECK: hlfir.destroy %[[VAL_5]] : !hlfir.expr<10x20xf32> 182! CHECK: return 183! CHECK: } 184