xref: /llvm-project/flang/test/Lower/HLFIR/where.f90 (revision 81ea91a9b4983738bcea5e7a77677c0f84b9f9d6)
1! Test lowering of WHERE construct and statements to HLFIR.
2! RUN: bbc -emit-hlfir -o - %s | FileCheck %s
3
4module where_defs
5  logical :: mask(10)
6  real :: x(10), y(10)
7  real, allocatable :: a(:), b(:)
8  interface
9    function return_temporary_mask()
10      logical, allocatable :: return_temporary_mask(:)
11    end function
12    function return_temporary_array()
13      real, allocatable :: return_temporary_array(:)
14    end function
15  end interface
16end module
17
18subroutine simple_where()
19  use where_defs, only: mask, x, y
20  where (mask) x = y
21end subroutine
22! CHECK-LABEL:   func.func @_QPsimple_where() {
23! CHECK:  %[[VAL_3:.*]]:2 = hlfir.declare {{.*}}Emask
24! CHECK:  %[[VAL_7:.*]]:2 = hlfir.declare {{.*}}Ex
25! CHECK:  %[[VAL_11:.*]]:2 = hlfir.declare {{.*}}Ey
26! CHECK:  hlfir.where {
27! CHECK:    hlfir.yield %[[VAL_3]]#0 : !fir.ref<!fir.array<10x!fir.logical<4>>>
28! CHECK:  } do {
29! CHECK:    hlfir.region_assign {
30! CHECK:      hlfir.yield %[[VAL_11]]#0 : !fir.ref<!fir.array<10xf32>>
31! CHECK:    } to {
32! CHECK:      hlfir.yield %[[VAL_7]]#0 : !fir.ref<!fir.array<10xf32>>
33! CHECK:    }
34! CHECK:  }
35! CHECK:  return
36! CHECK:}
37
38subroutine where_construct()
39  use where_defs
40  where (mask)
41    x = y
42    a = b
43  end where
44end subroutine
45! CHECK-LABEL:   func.func @_QPwhere_construct() {
46! CHECK:  %[[VAL_1:.*]]:2 = hlfir.declare %{{.*}} {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QMwhere_defsEa"}
47! CHECK:  %[[VAL_3:.*]]:2 = hlfir.declare %{{.*}} {fortran_attrs = #fir.var_attrs<allocatable>, uniq_name = "_QMwhere_defsEb"}
48! CHECK:  %[[VAL_7:.*]]:2 = hlfir.declare {{.*}}Emask
49! CHECK:  %[[VAL_11:.*]]:2 = hlfir.declare {{.*}}Ex
50! CHECK:  %[[VAL_15:.*]]:2 = hlfir.declare {{.*}}Ey
51! CHECK:  hlfir.where {
52! CHECK:    hlfir.yield %[[VAL_7]]#0 : !fir.ref<!fir.array<10x!fir.logical<4>>>
53! CHECK:  } do {
54! CHECK:    hlfir.region_assign {
55! CHECK:      hlfir.yield %[[VAL_15]]#0 : !fir.ref<!fir.array<10xf32>>
56! CHECK:    } to {
57! CHECK:      hlfir.yield %[[VAL_11]]#0 : !fir.ref<!fir.array<10xf32>>
58! CHECK:    }
59! CHECK:    hlfir.region_assign {
60! CHECK:      %[[VAL_16:.*]] = fir.load %[[VAL_3]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
61! CHECK:      hlfir.yield %[[VAL_16]] : !fir.box<!fir.heap<!fir.array<?xf32>>>
62! CHECK:    } to {
63! CHECK:      %[[VAL_17:.*]] = fir.load %[[VAL_1]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
64! CHECK:      hlfir.yield %[[VAL_17]] : !fir.box<!fir.heap<!fir.array<?xf32>>>
65! CHECK:    }
66! CHECK:  }
67! CHECK:  return
68! CHECK:}
69
70subroutine where_cleanup()
71  use where_defs, only: x, return_temporary_mask, return_temporary_array
72  where (return_temporary_mask()) x = return_temporary_array()
73end subroutine
74! CHECK-LABEL:   func.func @_QPwhere_cleanup() {
75! CHECK:  %[[VAL_0:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?xf32>>> {bindc_name = ".result"}
76! CHECK:  %[[VAL_1:.*]] = fir.alloca !fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>> {bindc_name = ".result"}
77! CHECK:  %[[VAL_5:.*]]:2 = hlfir.declare {{.*}}Ex
78! CHECK:  hlfir.where {
79! CHECK:    %[[VAL_6:.*]] = fir.call @_QPreturn_temporary_mask() fastmath<contract> : () -> !fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>
80! CHECK:    fir.save_result %[[VAL_6]] to %[[VAL_1]] : !fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>>
81! CHECK:    %[[VAL_7:.*]]:2 = hlfir.declare %[[VAL_1]] {uniq_name = ".tmp.func_result"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>>)
82! CHECK:             %[[deref:.*]] = fir.load %[[VAL_7]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>>
83! CHECK:             %[[MustFree:.*]] = arith.constant false
84! CHECK:             %[[ResTemp:.*]] = hlfir.as_expr %[[deref]] move %[[MustFree]] : (!fir.box<!fir.heap<!fir.array<?x!fir.logical<4>>>>, i1) -> !hlfir.expr<?x!fir.logical<4>>
85! CHECK:             hlfir.yield %[[ResTemp]] : !hlfir.expr<?x!fir.logical<4>> cleanup {
86! CHECK:        fir.freemem
87! CHECK:    }
88! CHECK:  } do {
89! CHECK:    hlfir.region_assign {
90! CHECK:      %[[VAL_14:.*]] = fir.call @_QPreturn_temporary_array() fastmath<contract> : () -> !fir.box<!fir.heap<!fir.array<?xf32>>>
91! CHECK:      fir.save_result %[[VAL_14]] to %[[VAL_0]] : !fir.box<!fir.heap<!fir.array<?xf32>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
92! CHECK:      %[[VAL_15:.*]]:2 = hlfir.declare %[[VAL_0]] {uniq_name = ".tmp.func_result"} : (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>) -> (!fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>, !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>)
93! CHECK:               %[[deref:.*]] = fir.load %[[VAL_15]]#0 : !fir.ref<!fir.box<!fir.heap<!fir.array<?xf32>>>>
94! CHECK:               %[[MustFree:.*]] = arith.constant false
95! CHECK:               %[[ResTemp:.*]] = hlfir.as_expr %[[deref]] move %[[MustFree]] : (!fir.box<!fir.heap<!fir.array<?xf32>>>, i1) -> !hlfir.expr<?xf32>
96! CHECK:               hlfir.yield %[[ResTemp]] : !hlfir.expr<?xf32> cleanup {
97! CHECK:          fir.freemem
98! CHECK:      }
99! CHECK:    } to {
100! CHECK:      hlfir.yield %[[VAL_5]]#0 : !fir.ref<!fir.array<10xf32>>
101! CHECK:    }
102! CHECK:  }
103
104subroutine simple_elsewhere()
105  use where_defs
106  where (mask)
107    x = y
108  elsewhere
109    y = x
110  end where
111end subroutine
112! CHECK-LABEL:   func.func @_QPsimple_elsewhere() {
113! CHECK:  %[[VAL_7:.*]]:2 = hlfir.declare {{.*}}Emask
114! CHECK:  %[[VAL_11:.*]]:2 = hlfir.declare {{.*}}Ex
115! CHECK:  %[[VAL_15:.*]]:2 = hlfir.declare {{.*}}Ey
116! CHECK:  hlfir.where {
117! CHECK:    hlfir.yield %[[VAL_7]]#0 : !fir.ref<!fir.array<10x!fir.logical<4>>>
118! CHECK:  } do {
119! CHECK:    hlfir.region_assign {
120! CHECK:      hlfir.yield %[[VAL_15]]#0 : !fir.ref<!fir.array<10xf32>>
121! CHECK:    } to {
122! CHECK:      hlfir.yield %[[VAL_11]]#0 : !fir.ref<!fir.array<10xf32>>
123! CHECK:    }
124! CHECK:    hlfir.elsewhere do {
125! CHECK:      hlfir.region_assign {
126! CHECK:        hlfir.yield %[[VAL_11]]#0 : !fir.ref<!fir.array<10xf32>>
127! CHECK:      } to {
128! CHECK:        hlfir.yield %[[VAL_15]]#0 : !fir.ref<!fir.array<10xf32>>
129! CHECK:      }
130! CHECK:    }
131! CHECK:  }
132
133subroutine elsewhere_2(mask2)
134  use where_defs, only : mask, x, y
135  logical :: mask2(:)
136  where (mask)
137    x = y
138  elsewhere(mask2)
139    y = x
140  elsewhere
141    x = foo()
142  end where
143end subroutine
144! CHECK-LABEL:   func.func @_QPelsewhere_2(
145! CHECK:  %[[VAL_5:.*]]:2 = hlfir.declare {{.*}}Emask
146! CHECK:  %[[VAL_6:.*]]:2 = hlfir.declare {{.*}}Emask2
147! CHECK:  %[[VAL_11:.*]]:2 = hlfir.declare {{.*}}Ex
148! CHECK:  %[[VAL_15:.*]]:2 = hlfir.declare {{.*}}Ey
149! CHECK:  hlfir.where {
150! CHECK:    hlfir.yield %[[VAL_5]]#0 : !fir.ref<!fir.array<10x!fir.logical<4>>>
151! CHECK:  } do {
152! CHECK:    hlfir.region_assign {
153! CHECK:      hlfir.yield %[[VAL_15]]#0 : !fir.ref<!fir.array<10xf32>>
154! CHECK:    } to {
155! CHECK:      hlfir.yield %[[VAL_11]]#0 : !fir.ref<!fir.array<10xf32>>
156! CHECK:    }
157! CHECK:    hlfir.elsewhere mask {
158! CHECK:      hlfir.yield %[[VAL_6]]#0 : !fir.box<!fir.array<?x!fir.logical<4>>>
159! CHECK:    } do {
160! CHECK:      hlfir.region_assign {
161! CHECK:        hlfir.yield %[[VAL_11]]#0 : !fir.ref<!fir.array<10xf32>>
162! CHECK:      } to {
163! CHECK:        hlfir.yield %[[VAL_15]]#0 : !fir.ref<!fir.array<10xf32>>
164! CHECK:      }
165! CHECK:      hlfir.elsewhere do {
166! CHECK:        hlfir.region_assign {
167! CHECK:          %[[VAL_16:.*]] = fir.call @_QPfoo() fastmath<contract> : () -> f32
168! CHECK:          hlfir.yield %[[VAL_16]] : f32
169! CHECK:        } to {
170! CHECK:          hlfir.yield %[[VAL_11]]#0 : !fir.ref<!fir.array<10xf32>>
171! CHECK:        }
172! CHECK:      }
173! CHECK:    }
174! CHECK:  }
175