File: array-copy.f90

package info (click to toggle)
swiftlang 6.0.3-2
  • links: PTS, VCS
  • area: main
  • in suites: forky, sid, trixie
  • size: 2,519,992 kB
  • sloc: cpp: 9,107,863; ansic: 2,040,022; asm: 1,135,751; python: 296,500; objc: 82,456; f90: 60,502; lisp: 34,951; pascal: 19,946; sh: 18,133; perl: 7,482; ml: 4,937; javascript: 4,117; makefile: 3,840; awk: 3,535; xml: 914; fortran: 619; cs: 573; ruby: 573
file content (144 lines) | stat: -rw-r--r-- 4,627 bytes parent folder | download | duplicates (5)
1
2
3
4
5
6
7
8
9
10
11
12
13
14
15
16
17
18
19
20
21
22
23
24
25
26
27
28
29
30
31
32
33
34
35
36
37
38
39
40
41
42
43
44
45
46
47
48
49
50
51
52
53
54
55
56
57
58
59
60
61
62
63
64
65
66
67
68
69
70
71
72
73
74
75
76
77
78
79
80
81
82
83
84
85
86
87
88
89
90
91
92
93
94
95
96
97
98
99
100
101
102
103
104
105
106
107
108
109
110
111
112
113
114
115
116
117
118
119
120
121
122
123
124
125
126
127
128
129
130
131
132
133
134
135
136
137
138
139
140
141
142
143
144
! Test array-value-copy
  
! RUN: bbc %s -o - | FileCheck %s

! Copy not needed
! CHECK-LABEL: func @_QPtest1(
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK-NOT:   ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK-NOT:     fir.freemem %
! CHECK:         return
! CHECK:       }
subroutine test1(a)
  integer :: a(3)

  a = a + 1
end subroutine test1

! Copy not needed
! CHECK-LABEL: func @_QPtest2(
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK-NOT:   ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK-NOT:     fir.freemem %
! CHECK:         return
! CHECK:       }
subroutine test2(a, b)
  integer :: a(3), b(3)

  a = b + 1
end subroutine test2

! Copy not needed
! CHECK-LABEL: func @_QPtest3(
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK-NOT:   ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK-NOT:     fir.freemem %
! CHECK:         return
! CHECK:       }
subroutine test3(a)
  integer :: a(3)

  forall (i=1:3)
     a(i) = a(i) + 1
  end forall
end subroutine test3

! Make a copy. (Crossing dependence)
! CHECK-LABEL: func @_QPtest4(
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:         fir.freemem %{{.*}} : !fir.heap<!fir.array<3xi32>>
! CHECK:         return
! CHECK:       }
subroutine test4(a)
  integer :: a(3)

  forall (i=1:3)
     a(i) = a(4-i) + 1
  end forall
end subroutine test4

! Make a copy. (Carried dependence)
! CHECK-LABEL: func @_QPtest5(
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:         fir.freemem %{{.*}} : !fir.heap<!fir.array<3xi32>>
! CHECK:         return
! CHECK:       }
subroutine test5(a)
  integer :: a(3)

  forall (i=2:3)
     a(i) = a(i-1) + 14
  end forall
end subroutine test5

! Make a copy. (Carried dependence)
! CHECK-LABEL: func @_QPtest6(
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:         fir.freemem %{{.*}} : !fir.heap<!fir.array<3x!fir.type<_QFtest6Tt{m:!fir.array<3xi32>}>>>
! CHECK:         return
! CHECK:       }
subroutine test6(a)
  type t
     integer :: m(3)
  end type t
  type(t) :: a(3)

  forall (i=2:3)
     a(i)%m = a(i-1)%m + 14
  end forall
end subroutine test6

! Make a copy. (Overlapping partial CHARACTER update.)
! CHECK-LABEL: func @_QPtest7(
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:         fir.freemem %{{.*}} : !fir.heap<!fir.array<3x!fir.char<1,8>>>
! CHECK:         return
! CHECK:       }
subroutine test7(a)
  character(8) :: a(3)

  a(:)(2:5) = a(:)(3:6)
end subroutine test7

! Do not make a copy.
! CHECK-LABEL: func @_QPtest8(
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:       ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK-NOT:   ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK-NOT:     fir.freemem %
! CHECK:         return
! CHECK:       }
subroutine test8(a,b)
  character(8) :: a(3), b(3)

  a(:)(2:5) = b(:)(3:6)
end subroutine test8

! Do make a copy. Assume vector subscripts cause dependences.
! CHECK-LABEL: func @_QPtest9(
! CHECK-SAME: %[[a:[^:]+]]: !fir.ref<!fir.array<?x?xf32>>
! CHECK: %[[und:.*]] = fir.undefined index
! CHECK: %[[slice:.*]] = fir.slice %[[und]], %[[und]], %[[und]],
! CHECK: %[[heap:.*]] = fir.allocmem !fir.array<?x?xf32>, %{{.*}}, %{{.*}}
! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:   ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:   ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK: = fir.array_coor %[[a]](%{{.*}}) [%[[slice]]] %{{.*}}, %{{.*}} : (!fir.ref<!fir.array<?x?xf32>>, !fir.shape<2>, !fir.slice<2>, index, index) -> !fir.ref<f32>
! CHECK: = fir.array_coor %[[heap]](%{{.*}}) [%[[slice]]] %{{.*}}, %{{.*}} : (!fir.heap<!fir.array<?x?xf32>>, !fir.shape<2>, !fir.slice<2>, index, index) -> !fir.ref<f32>
! CHECK: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK:   ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK-NOT: ^bb{{[0-9]+}}(%{{.*}}: index, %{{.*}}: index):
! CHECK: fir.freemem %[[heap]]
subroutine test9(a,v1,v2,n)
  real :: a(n,n)
  integer :: v1(n), v2(n)
  a(v1,:) = a(v2,:)
end subroutine test9