Skip to content

Commit 0e99705

Browse files
authored
Merge pull request #1174 from schweitzpgi/ch-test
Add an array value copy test.
2 parents d61310e + 18fc076 commit 0e99705

File tree

1 file changed

+122
-0
lines changed

1 file changed

+122
-0
lines changed

flang/test/Lower/array-copy.f90

Lines changed: 122 additions & 0 deletions
Original file line numberDiff line numberDiff line change
@@ -0,0 +1,122 @@
1+
! Test array-value-copy
2+
3+
! RUN: bbc %s -o - | FileCheck %s
4+
5+
! Copy not needed
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 %
10+
! CHECK: return
11+
! CHECK: }
12+
subroutine test1(a)
13+
integer :: a(3)
14+
15+
a = a + 1
16+
end subroutine test1
17+
18+
! Copy not needed
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 %
23+
! CHECK: return
24+
! CHECK: }
25+
subroutine test2(a, b)
26+
integer :: a(3), b(3)
27+
28+
a = b + 1
29+
end subroutine test2
30+
31+
! Copy not needed
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 %
36+
! CHECK: return
37+
! CHECK: }
38+
subroutine test3(a)
39+
integer :: a(3)
40+
41+
forall (i=1:3)
42+
a(i) = a(i) + 1
43+
end forall
44+
end subroutine test3
45+
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>>
51+
! CHECK: return
52+
! CHECK: }
53+
subroutine test4(a)
54+
integer :: a(3)
55+
56+
forall (i=1:3)
57+
a(i) = a(4-i) + 1
58+
end forall
59+
end subroutine test4
60+
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>>
66+
! CHECK: return
67+
! CHECK: }
68+
subroutine test5(a)
69+
integer :: a(3)
70+
71+
forall (i=2:3)
72+
a(i) = a(i-1) + 14
73+
end forall
74+
end subroutine test5
75+
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>}>>>
81+
! CHECK: return
82+
! CHECK: }
83+
subroutine test6(a)
84+
type t
85+
integer :: m(3)
86+
end type t
87+
type(t) :: a(3)
88+
89+
forall (i=2:3)
90+
a(i)%m = a(i-1)%m + 14
91+
end forall
92+
end subroutine test6
93+
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>>>
101+
! CHECK: return
102+
! CHECK: }
103+
subroutine test7(a)
104+
character(8) :: a(3)
105+
106+
a(:)(2:5) = a(:)(3:6)
107+
end subroutine test7
108+
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 %
116+
! CHECK: return
117+
! CHECK: }
118+
subroutine test8(a,b)
119+
character(8) :: a(3), b(3)
120+
121+
a(:)(2:5) = b(:)(3:6)
122+
end subroutine test8

0 commit comments

Comments
 (0)