xref: /llvm-project/flang/test/Lower/array-elemental-calls-3.f90 (revision f35f863a88f83332bef9605ef4cfe4f05c066efb)
1*f35f863aSjeanPerier! RUN: bbc -o - -emit-fir -hlfir=false %s | FileCheck %s
2c881f3ebSLeandro Lupori
3c881f3ebSLeandro Lupori! Test lowering of elemental calls with array arguments that use array
4c881f3ebSLeandro Lupori! elements as indices.
5c881f3ebSLeandro Lupori! As reported in issue #62981, wrong code was being generated in this case.
6c881f3ebSLeandro Lupori
7c881f3ebSLeandro Luporimodule test_ops
8c881f3ebSLeandro Lupori  implicit none
9c881f3ebSLeandro Lupori  interface
10c881f3ebSLeandro Lupori    integer elemental function elem_func_i(i)
11c881f3ebSLeandro Lupori      integer, intent(in) :: i
12c881f3ebSLeandro Lupori    end function
13c881f3ebSLeandro Lupori    real elemental function elem_func_r(r)
14c881f3ebSLeandro Lupori      real, intent(in) :: r
15c881f3ebSLeandro Lupori    end function
16c881f3ebSLeandro Lupori  end interface
17c881f3ebSLeandro Lupori
18c881f3ebSLeandro Lupori  integer :: a(3), b(3), v(3), i, j, k, l
19c881f3ebSLeandro Lupori  real :: x(2), y(2), u
20c881f3ebSLeandro Lupori
21c881f3ebSLeandro Luporicontains
22c881f3ebSLeandro Lupori! CHECK-LABEL: func @_QMtest_opsPcheck_array_elems_as_indices() {
23c881f3ebSLeandro Luporisubroutine check_array_elems_as_indices()
24c881f3ebSLeandro Lupori! CHECK: %[[A_ADDR:.*]] = fir.address_of(@_QMtest_opsEa) : !fir.ref<!fir.array<3xi32>>
25c881f3ebSLeandro Lupori! CHECK: %[[V_ADDR:.*]] = fir.address_of(@_QMtest_opsEv) : !fir.ref<!fir.array<3xi32>>
26c881f3ebSLeandro Lupori! CHECK: %[[V:.*]] = fir.array_load %[[V_ADDR]](%{{.*}}) : (!fir.ref<!fir.array<3xi32>>, !fir.shape<1>) -> !fir.array<3xi32>
27c881f3ebSLeandro Lupori! CHECK: %[[A:.*]] = fir.array_load %[[A_ADDR]](%{{.*}}) : (!fir.ref<!fir.array<3xi32>>, !fir.shape<1>) -> !fir.array<3xi32>
28c881f3ebSLeandro Lupori! CHECK: fir.do_loop
29c881f3ebSLeandro Lupori  forall (i=1:3)
30c881f3ebSLeandro Lupori! CHECK: %{{.*}} = fir.array_fetch %[[V]], %{{.*}} : (!fir.array<3xi32>, index) -> i32
31c881f3ebSLeandro Lupori! CHECK: fir.do_loop
32c881f3ebSLeandro Lupori! CHECK: %[[ELEM:.*]] = fir.array_access %[[A]], %{{.*}} : (!fir.array<3xi32>, index) -> !fir.ref<i32>
33c881f3ebSLeandro Lupori! CHECK: %{{.*}} = fir.call @_QPelem_func_i(%[[ELEM]]){{.*}} : (!fir.ref<i32>) -> i32
34c881f3ebSLeandro Lupori    b(i:i) = elem_func_i(a(v(i):v(i)))
35c881f3ebSLeandro Lupori  end forall
36c881f3ebSLeandro Luporiend subroutine
37c881f3ebSLeandro Lupori
38c881f3ebSLeandro Lupori! CHECK-LABEL: func @_QMtest_opsPcheck_not_assert() {
39c881f3ebSLeandro Luporisubroutine check_not_assert()
40c881f3ebSLeandro Lupori  ! Implicit path.
41c881f3ebSLeandro Lupori  b = 10 + elem_func_i(a)
42c881f3ebSLeandro Lupori
43c881f3ebSLeandro Lupori  ! Expression as argument, instead of variable.
44c881f3ebSLeandro Lupori  forall (i=1:3)
45c881f3ebSLeandro Lupori    b(i:i) = elem_func_i(a(i:i) + a(i:i))
46c881f3ebSLeandro Lupori  end forall
47c881f3ebSLeandro Lupori
48c881f3ebSLeandro Lupori  ! Nested elemental function calls.
49c881f3ebSLeandro Lupori  y = elem_func_r(cos(x))
50c881f3ebSLeandro Lupori  y = elem_func_r(cos(x) + u)
51c881f3ebSLeandro Lupori
52c881f3ebSLeandro Lupori  ! Array constructors as elemental function arguments.
536fac3f7bSPeter Klausler  y = atan2( (/ (real(i, 4), i = 1, 2) /), &
54c881f3ebSLeandro Lupori             real( (/ (i, i = j, k, l) /), 4) )
55c881f3ebSLeandro Luporiend subroutine
56c881f3ebSLeandro Lupori
57c881f3ebSLeandro Luporiend module
58