IR: de-duplicate two CmpInst routines (NFC) (#116866)
[llvm-project.git] / flang / test / Lower / loops2.f90
blob0a587234a991b698ae56b23da115ec3109d75818
1 ! Test loop variables increment
2 ! RUN: bbc -emit-fir -hlfir=false -o - %s | FileCheck %s
4 module test_loop_var
5 implicit none
6 integer, pointer:: i_pointer
7 integer, allocatable :: i_allocatable
8 real, pointer :: x_pointer
9 real, allocatable :: x_allocatable
10 contains
11 ! CHECK-LABEL: func @_QMtest_loop_varPtest_pointer
12 subroutine test_pointer()
13 do i_pointer=1,10
14 enddo
15 ! CHECK: %[[VAL_0:.*]] = fir.address_of(@_QMtest_loop_varEi_pointer) : !fir.ref<!fir.box<!fir.ptr<i32>>>
16 ! CHECK: %[[VAL_1:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.ptr<i32>>>
17 ! CHECK: %[[VAL_2:.*]] = fir.box_addr %[[VAL_1]] : (!fir.box<!fir.ptr<i32>>) -> !fir.ptr<i32>
18 ! CHECK: %[[VAL_9:.*]]:2 = fir.do_loop{{.*}}iter_args(%[[IV:.*]] = {{.*}})
19 ! CHECK: fir.store %[[IV]] to %[[VAL_2]] : !fir.ptr<i32>
20 ! CHECK: }
21 ! CHECK: fir.store %[[VAL_9]]#1 to %[[VAL_2]] : !fir.ptr<i32>
22 end subroutine
24 ! CHECK-LABEL: func @_QMtest_loop_varPtest_allocatable
25 subroutine test_allocatable()
26 do i_allocatable=1,10
27 enddo
28 ! CHECK: %[[VAL_0:.*]] = fir.address_of(@_QMtest_loop_varEi_allocatable) : !fir.ref<!fir.box<!fir.heap<i32>>>
29 ! CHECK: %[[VAL_1:.*]] = fir.load %[[VAL_0]] : !fir.ref<!fir.box<!fir.heap<i32>>>
30 ! CHECK: %[[VAL_2:.*]] = fir.box_addr %[[VAL_1]] : (!fir.box<!fir.heap<i32>>) -> !fir.heap<i32>
31 ! CHECK: %[[VAL_9:.*]]:2 = fir.do_loop{{.*}}iter_args(%[[IV:.*]] = {{.*}})
32 ! CHECK: fir.store %[[IV]] to %[[VAL_2]] : !fir.heap<i32>
33 ! CHECK: }
34 ! CHECK: fir.store %[[VAL_9]]#1 to %[[VAL_2]] : !fir.heap<i32>
35 end subroutine
37 ! CHECK-LABEL: func @_QMtest_loop_varPtest_real_pointer
38 subroutine test_real_pointer()
39 do x_pointer=1,10
40 enddo
41 ! CHECK: %[[VAL_0:.*]] = fir.alloca index
42 ! CHECK: %[[VAL_1:.*]] = fir.address_of(@_QMtest_loop_varEx_pointer) : !fir.ref<!fir.box<!fir.ptr<f32>>>
43 ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]] : !fir.ref<!fir.box<!fir.ptr<f32>>>
44 ! CHECK: %[[VAL_3:.*]] = fir.box_addr %[[VAL_2]] : (!fir.box<!fir.ptr<f32>>) -> !fir.ptr<f32>
45 ! CHECK: %[[VAL_4:.*]] = arith.constant 1 : i32
46 ! CHECK: %[[VAL_5:.*]] = fir.convert %[[VAL_4]] : (i32) -> f32
47 ! CHECK: %[[VAL_8:.*]] = arith.constant 1.000000e+00 : f32
49 ! CHECK: fir.store %[[VAL_5]] to %[[VAL_3]] : !fir.ptr<f32>
50 ! CHECK: br ^bb1
51 ! CHECK: ^bb1:
52 ! CHECK: cond_br %{{.*}}, ^bb2, ^bb3
53 ! CHECK: ^bb2:
54 ! CHECK: %[[VAL_19:.*]] = fir.load %[[VAL_3]] : !fir.ptr<f32>
55 ! CHECK: %[[VAL_20:.*]] = arith.constant 1.000000e+00 : f32
56 ! CHECK: %[[VAL_21:.*]] = arith.addf %[[VAL_19]], %[[VAL_20]] {{.*}}: f32
57 ! CHECK: fir.store %[[VAL_21]] to %[[VAL_3]] : !fir.ptr<f32>
58 ! CHECK: br ^bb1
59 ! CHECK: ^bb3:
60 ! CHECK: return
61 end subroutine
63 ! CHECK-LABEL: func @_QMtest_loop_varPtest_real_allocatable
64 subroutine test_real_allocatable()
65 do x_allocatable=1,10
66 enddo
67 ! CHECK: %[[VAL_0:.*]] = fir.alloca index
68 ! CHECK: %[[VAL_1:.*]] = fir.address_of(@_QMtest_loop_varEx_allocatable) : !fir.ref<!fir.box<!fir.heap<f32>>>
69 ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]] : !fir.ref<!fir.box<!fir.heap<f32>>>
70 ! CHECK: %[[VAL_3:.*]] = fir.box_addr %[[VAL_2]] : (!fir.box<!fir.heap<f32>>) -> !fir.heap<f32>
71 ! CHECK: %[[VAL_4:.*]] = arith.constant 1 : i32
72 ! CHECK: %[[VAL_5:.*]] = fir.convert %[[VAL_4]] : (i32) -> f32
73 ! CHECK: %[[VAL_8:.*]] = arith.constant 1.000000e+00 : f32
75 ! CHECK: fir.store %[[VAL_5]] to %[[VAL_3]] : !fir.heap<f32>
76 ! CHECK: br ^bb1
77 ! CHECK: ^bb1:
78 ! CHECK: cond_br %{{.*}}, ^bb2, ^bb3
79 ! CHECK: ^bb2:
80 ! CHECK: %[[VAL_19:.*]] = fir.load %[[VAL_3]] : !fir.heap<f32>
81 ! CHECK: %[[VAL_20:.*]] = arith.constant 1.000000e+00 : f32
82 ! CHECK: %[[VAL_21:.*]] = arith.addf %[[VAL_19]], %[[VAL_20]] {{.*}}: f32
83 ! CHECK: fir.store %[[VAL_21]] to %[[VAL_3]] : !fir.heap<f32>
84 ! CHECK: br ^bb1
85 ! CHECK: ^bb3:
86 ! CHECK: return
87 end subroutine
89 ! CHECK-LABEL: func @_QMtest_loop_varPtest_pointer_unstructured_loop()
90 subroutine test_pointer_unstructured_loop()
91 do i_pointer=1,10
92 if (i_pointer .gt. 5) exit
93 enddo
94 ! CHECK: %[[VAL_1:.*]] = fir.address_of(@_QMtest_loop_varEi_pointer) : !fir.ref<!fir.box<!fir.ptr<i32>>>
95 ! CHECK: %[[VAL_2:.*]] = fir.load %[[VAL_1]] : !fir.ref<!fir.box<!fir.ptr<i32>>>
96 ! CHECK: %[[VAL_3:.*]] = fir.box_addr %[[VAL_2]] : (!fir.box<!fir.ptr<i32>>) -> !fir.ptr<i32>
97 ! CHECK: %[[VAL_4:.*]] = arith.constant 1 : i32
98 ! CHECK: %[[VAL_6:.*]] = arith.constant 1 : i32
99 ! CHECK: fir.store %[[VAL_4]] to %[[VAL_3]] : !fir.ptr<i32>
100 ! CHECK: br ^bb1
101 ! CHECK: ^bb1:
102 ! CHECK: cond_br %{{.*}}, ^bb2, ^bb5
103 ! CHECK: ^bb2:
104 ! CHECK: cond_br %{{.*}}, ^bb3, ^bb4
105 ! CHECK: ^bb3:
106 ! CHECK: br ^bb5
107 ! CHECK: ^bb4:
108 ! CHECK: %[[VAL_20:.*]] = fir.load %[[VAL_3]] : !fir.ptr<i32>
109 ! CHECK: %[[VAL_21:.*]] = arith.constant 1 : i32
110 ! CHECK: %[[VAL_22:.*]] = arith.addi %[[VAL_20]], %[[VAL_21]] : i32
111 ! CHECK: fir.store %[[VAL_22]] to %[[VAL_3]] : !fir.ptr<i32>
112 ! CHECK: br ^bb1
113 ! CHECK: ^bb5:
114 ! CHECK: return
115 ! CHECK: }
116 end subroutine
118 end module
120 use test_loop_var
121 implicit none
122 integer, target :: i_target = -1
123 real, target :: x_target = -1.
124 i_pointer => i_target
125 allocate(i_allocatable)
126 i_allocatable = -1
127 x_pointer => x_target
128 allocate(x_allocatable)
129 x_allocatable = -1.
131 call test_pointer()
132 call test_allocatable()
133 call test_real_pointer()
134 call test_real_allocatable()
135 ! Expect 11 everywhere
136 print *, i_target
137 print *, i_allocatable
138 print *, x_target
139 print *, x_allocatable
141 call test_pointer_unstructured_loop()
142 call test_allocatable_unstructured_loop()
143 ! Expect 6 everywhere
144 print *, i_target