xref: /llvm-project/flang/test/HLFIR/order_assignments/where-hoisting.f90 (revision c7c5666aac543a49b485a133f4a94865e2613a43)
1! Test that scalar expressions are not hoisted from WHERE loops
2! when they do not appear
3! RUN: bbc -hlfir -o - -pass-pipeline="builtin.module(lower-hlfir-ordered-assignments)" %s | FileCheck %s
4
5subroutine do_not_hoist_div(n, mask, a)
6  integer :: a(10), n
7  logical :: mask(10)
8  where(mask) a=1/n
9end subroutine
10! CHECK-LABEL:   func.func @_QPdo_not_hoist_div(
11! CHECK-NOT:       arith.divsi
12! CHECK:           fir.do_loop {{.*}} {
13! CHECK:             fir.if {{.*}} {
14! CHECK:               arith.divsi
15! CHECK:             }
16! CHECK:           }
17
18subroutine do_not_hoist_optional(n, mask, a)
19  integer :: a(10)
20  integer, optional :: n
21  logical :: mask(10)
22  where(mask) a=n
23end subroutine
24! CHECK-LABEL:   func.func @_QPdo_not_hoist_optional(
25! CHECK:           %[[VAL_9:.*]]:2 = hlfir.declare {{.*}}"_QFdo_not_hoist_optionalEn"
26! CHECK-NOT:       fir.load %[[VAL_9]]
27! CHECK:           fir.do_loop {{.*}} {
28! CHECK:             fir.if {{.*}} {
29! CHECK:               %[[VAL_15:.*]] = fir.load %[[VAL_9]]#0 : !fir.ref<i32>
30! CHECK:             }
31! CHECK:           }
32
33subroutine hoist_function(n, mask, a)
34  integer :: a(10, 10)
35  integer, optional :: n
36  logical :: mask(10, 10)
37  forall (i=1:10)
38  where(mask(i, :)) a(i,:)=ihoist_me(i)
39  end forall
40end subroutine
41! CHECK-LABEL:   func.func @_QPhoist_function(
42! CHECK:           fir.do_loop {{.*}} {
43! CHECK:             fir.call @_QPihoist_me
44! CHECK:             fir.do_loop {{.*}} {
45! CHECK:               fir.if %{{.*}} {
46! CHECK-NOT:             fir.call @_QPihoist_me
47! CHECK:               }
48! CHECK:             }
49! CHECK:           }
50! CHECK-NOT:       fir.call @_QPihoist_me
51