1 ! Test array-value-copy
3 ! RUN: bbc -hlfir=false %s -o - | FileCheck %s
6 ! CHECK-LABEL: func @_QPtest1(
7 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
8 ! CHECK-NOT: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
9 ! CHECK-NOT: fir.freemem %
19 ! CHECK-LABEL: func @_QPtest2(
20 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
21 ! CHECK-NOT: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
22 ! CHECK-NOT: fir.freemem %
25 subroutine test2(a
, b
)
32 ! CHECK-LABEL: func @_QPtest3(
33 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
34 ! CHECK-NOT: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
35 ! CHECK-NOT: fir.freemem %
46 ! Make a copy. (Crossing dependence)
47 ! CHECK-LABEL: func @_QPtest4(
48 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
49 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
50 ! CHECK: fir.freemem %{{.*}} : !fir.heap<!fir.array<3xi32>>
61 ! Make a copy. (Carried dependence)
62 ! CHECK-LABEL: func @_QPtest5(
63 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
64 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
65 ! CHECK: fir.freemem %{{.*}} : !fir.heap<!fir.array<3xi32>>
76 ! Make a copy. (Carried dependence)
77 ! CHECK-LABEL: func @_QPtest6(
78 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
79 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
80 ! CHECK: fir.freemem %{{.*}} : !fir.heap<!fir.array<3x!fir.type<_QFtest6Tt{m:!fir.array<3xi32>}>>>
90 a(i
)%m
= a(i
-1)%m
+ 14
94 ! Make a copy. (Overlapping partial CHARACTER update.)
95 ! CHECK-LABEL: func @_QPtest7(
96 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
97 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
98 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
99 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
100 ! CHECK: fir.freemem %{{.*}} : !fir.heap<!fir.array<3x!fir.char<1,8>>>
106 a(:)(2:5) = a(:)(3:6)
109 ! Do not make a copy.
110 ! CHECK-LABEL: func @_QPtest8(
111 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
112 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
113 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
114 ! CHECK-NOT: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
115 ! CHECK-NOT: fir.freemem %
118 subroutine test8(a
,b
)
119 character(8) :: a(3), b(3)
121 a(:)(2:5) = b(:)(3:6)
124 ! Do make a copy. Assume vector subscripts cause dependences.
125 ! CHECK-LABEL: func @_QPtest9(
126 ! CHECK-SAME: %[[a:[^:]+]]: !fir.ref<!fir.array<?x?xf32>>
127 ! CHECK: %[[und:.*]] = fir.undefined index
128 ! CHECK: %[[slice:.*]] = fir.slice %[[und]], %[[und]], %[[und]],
129 ! CHECK: %[[heap:.*]] = fir.allocmem !fir.array<?x?xf32>, %{{.*}}, %{{.*}}
130 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
131 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
132 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
133 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
134 ! CHECK: = fir.array_coor %[[a]](%{{.*}}) [%[[slice]]] %{{.*}}, %{{.*}} : (!fir.ref<!fir.array<?x?xf32>>, !fir.shape<2>, !fir.slice<2>, index, index) -> !fir.ref<f32>
135 ! CHECK: = fir.array_coor %[[heap]](%{{.*}}) [%[[slice]]] %{{.*}}, %{{.*}} : (!fir.heap<!fir.array<?x?xf32>>, !fir.shape<2>, !fir.slice<2>, index, index) -> !fir.ref<f32>
136 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
137 ! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
138 ! CHECK-NOT: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
139 ! CHECK: fir.freemem %[[heap]]
140 subroutine test9(a
,v1
,v2
,n
)
142 integer :: v1(n
), v2(n
)