1 ! RUN: bbc -o - -emit-fir -hlfir=false %s | FileCheck %s
3 ! Test lowering of elemental calls with array arguments that use array
5 ! As reported in issue #62981, wrong code was being generated in this case.
10 integer elemental
function elem_func_i(i
)
11 integer, intent(in
) :: i
13 real elemental
function elem_func_r(r
)
18 integer :: a(3), b(3), v(3), i
, j
, k
, l
22 ! CHECK-LABEL: func @_QMtest_opsPcheck_array_elems_as_indices() {
23 subroutine check_array_elems_as_indices()
24 ! CHECK: %[[A_ADDR:.*]] = fir.address_of(@_QMtest_opsEa) : !fir.ref<!fir.array<3xi32>>
25 ! CHECK: %[[V_ADDR:.*]] = fir.address_of(@_QMtest_opsEv) : !fir.ref<!fir.array<3xi32>>
26 ! CHECK: %[[V:.*]] = fir.array_load %[[V_ADDR]](%{{.*}}) : (!fir.ref<!fir.array<3xi32>>, !fir.shape<1>) -> !fir.array<3xi32>
27 ! CHECK: %[[A:.*]] = fir.array_load %[[A_ADDR]](%{{.*}}) : (!fir.ref<!fir.array<3xi32>>, !fir.shape<1>) -> !fir.array<3xi32>
30 ! CHECK: %{{.*}} = fir.array_fetch %[[V]], %{{.*}} : (!fir.array<3xi32>, index) -> i32
32 ! CHECK: %[[ELEM:.*]] = fir.array_access %[[A]], %{{.*}} : (!fir.array<3xi32>, index) -> !fir.ref<i32>
33 ! CHECK: %{{.*}} = fir.call @_QPelem_func_i(%[[ELEM]]){{.*}} : (!fir.ref<i32>) -> i32
34 b(i
:i
) = elem_func_i(a(v(i
):v(i
)))
38 ! CHECK-LABEL: func @_QMtest_opsPcheck_not_assert() {
39 subroutine check_not_assert()
41 b
= 10 + elem_func_i(a
)
43 ! Expression as argument, instead of variable.
45 b(i
:i
) = elem_func_i(a(i
:i
) + a(i
:i
))
48 ! Nested elemental function calls.
49 y
= elem_func_r(cos(x
))
50 y
= elem_func_r(cos(x
) + u
)
52 ! Array constructors as elemental function arguments.
53 y
= atan2( (/ (real(i
, 4), i
= 1, 2) /), &
54 real( (/ (i
, i
= j
, k
, l
) /), 4) )