xref: /llvm-project/flang/test/Lower/array.f90 (revision c4204c0b29a6721267b1bcbaeedd7b1118e42396)
1! RUN: bbc -hlfir=false -o - %s | FileCheck %s
2
3! CHECK-LABEL: fir.global @block_
4! CHECK-DAG: %[[VAL_1:.*]] = arith.constant 1.000000e+00 : f32
5! CHECK-DAG: %[[VAL_2:.*]] = arith.constant 2.400000e+00 : f32
6! CHECK-DAG: %[[VAL_3:.*]] = arith.constant 0.000000e+00 : f32
7! CHECK: %[[VAL_4:.*]] = fir.zero_bits tuple<!fir.array<5x5xf32>>
8! CHECK: %[[VAL_5:.*]] = fir.undefined !fir.array<5x5xf32>
9! CHECK: %[[VAL_6:.*]] = fir.insert_on_range %[[VAL_5]], %[[VAL_1]] from (0, 0) to (1, 0) : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
10! CHECK: %[[VAL_7:.*]] = fir.insert_on_range %[[VAL_6]], %[[VAL_3]] from (2, 0) to (4, 0) : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
11! CHECK: %[[VAL_8:.*]] = fir.insert_on_range %[[VAL_7]], %[[VAL_1]] from (0, 1) to (1, 1) : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
12! CHECK: %[[VAL_9:.*]] = fir.insert_value %[[VAL_8]], %[[VAL_3]], [2 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
13! CHECK: %[[VAL_10:.*]] = fir.insert_value %[[VAL_9]], %[[VAL_2]], [3 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
14! CHECK: %[[VAL_11:.*]] = fir.insert_value %[[VAL_10]], %[[VAL_3]], [4 : index, 1 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
15! CHECK: %[[VAL_12:.*]] = fir.insert_on_range %[[VAL_11]], %[[VAL_1]] from (0, 2) to (1, 2) : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
16! CHECK: %[[VAL_13:.*]] = fir.insert_value %[[VAL_12]], %[[VAL_3]], [2 : index, 2 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
17! CHECK: %[[VAL_14:.*]] = fir.insert_value %[[VAL_13]], %[[VAL_2]], [3 : index, 2 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
18! CHECK: %[[VAL_15:.*]] = fir.insert_on_range %[[VAL_14]], %[[VAL_3]] from (4, 2) to (2, 3) : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
19! CHECK: %[[VAL_16:.*]] = fir.insert_value %[[VAL_15]], %[[VAL_2]], [3 : index, 3 : index] : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
20! CHECK: %[[VAL_17:.*]] = fir.insert_on_range %[[VAL_16]], %[[VAL_3]] from (4, 3) to (4, 4) : (!fir.array<5x5xf32>, f32) -> !fir.array<5x5xf32>
21! CHECK: %[[VAL_18:.*]] = fir.insert_value %[[VAL_4]], %[[VAL_17]], [0 : index] : (tuple<!fir.array<5x5xf32>>, !fir.array<5x5xf32>) -> tuple<!fir.array<5x5xf32>>
22! CHECK: fir.has_value %[[VAL_18]] : tuple<!fir.array<5x5xf32>>
23
24subroutine s(i,j,k,ii,jj,kk,a1,a2,a3,a4,a5,a6,a7)
25  integer i, j, k, ii, jj, kk
26
27  ! extents are compile-time constant
28  real a1(10,20)
29  integer a2(30,*)
30  real a3(2:40,3:50)
31  integer a4(4:60, 5:*)
32
33  ! extents computed at run-time
34  real a5(i:j)
35  integer a6(6:i,j:*)
36  real a7(i:70,7:j,k:80)
37
38  ! CHECK-LABEL: BeginExternalListOutput
39  ! CHECK-DAG: fir.load %arg3 :
40  ! CHECK-DAG: %[[i1:.*]] = arith.subi %{{.*}}, %[[one:c1.*]] :
41  ! CHECK: fir.load %arg4 :
42  ! CHECK: %[[j1:.*]] = arith.subi %{{.*}}, %[[one]] :
43  ! CHECK: fir.coordinate_of %arg6, %[[i1]], %[[j1]] :
44  ! CHECK-LABEL: EndIoStatement
45  print *, a1(ii,jj)
46  ! CHECK-LABEL: BeginExternalListOutput
47  ! CHECK: fir.coordinate_of %{{[0-9]+}}, %{{[0-9]+}} : {{.*}} -> !fir.ref<i32>
48  ! CHECK-LABEL: EndIoStatement
49  print *, a2(ii,jj)
50  ! CHECK-LABEL: BeginExternalListOutput
51  ! CHECK-DAG: fir.load %arg3 :
52  ! CHECK-DAG: %[[cc2:.*]] = fir.convert %c2{{.*}} :
53  ! CHECK: %[[i2:.*]] = arith.subi %{{.*}}, %[[cc2]] :
54  ! CHECK-DAG: fir.load %arg4 :
55  ! CHECK-DAG: %[[cc3:.*]] = fir.convert %c3{{.*}} :
56  ! CHECK: %[[j2:.*]] = arith.subi %{{.*}}, %[[cc3]] :
57  ! CHECK: fir.coordinate_of %arg8, %[[i2]], %[[j2]] :
58  ! CHECK-LABEL: EndIoStatement
59  print *, a3(ii,jj)
60  ! CHECK-LABEL: BeginExternalListOutput
61  ! CHECK-LABEL: EndIoStatement
62  print *, a4(ii,jj)
63  ! CHECK-LABEL: BeginExternalListOutput
64  ! CHECK: fir.load %arg5 :
65  ! CHECK: %[[x5:.*]] = arith.subi %{{.*}}, %{{.*}} :
66  ! CHECK: fir.coordinate_of %arg10, %[[x5]] :
67  ! CHECK-LABEL: EndIoStatement
68  print *, a5(kk)
69  ! CHECK-LABEL: BeginExternalListOutput
70  ! CHECK: %[[a6:.*]] = fir.convert %arg11 : {{.*}} -> !fir.ref<!fir.array<?xi32>>
71  ! CHECK: fir.load %arg3 :
72  ! CHECK-DAG: %[[x6:.*]] = arith.subi %{{.*}}, %{{.*}} :
73  ! CHECK-DAG: fir.load %arg4 :
74  ! CHECK: %[[y6:.*]] = arith.subi %{{.*}}, %{{.*}} :
75  ! CHECK: %[[z6:.*]] = arith.muli %{{.}}, %[[y6]] :
76  ! CHECK: %[[w6:.*]] = arith.addi %[[z6]], %[[x6]] :
77  ! CHECK: fir.coordinate_of %[[a6]], %[[w6]] :
78  ! CHECK-LABEL: EndIoStatement
79  print *, a6(ii, jj)
80  ! CHECK-LABEL: BeginExternalListOutput
81  ! CHECK: %[[a7:.*]] = fir.convert %arg12 : {{.*}} -> !fir.ref<!fir.array<?xf32>>
82  ! CHECK: fir.load %arg5 :
83  ! CHECK-DAG: %[[x7:.*]] = arith.subi %{{.*}}, %{{.*}} :
84  ! CHECK-DAG: fir.load %arg4 :
85  ! CHECK: %[[y7:.*]] = arith.subi %{{.*}}, %{{.*}} :
86  ! CHECK: %[[z7:.*]] = arith.muli %[[u7:.*]], %[[y7]] :
87  ! CHECK: %[[w7:.*]] = arith.addi %[[z7]], %[[x7]] :
88  ! CHECK-DAG: %[[v7:.*]] = arith.muli %[[u7]], %{{.*}} :
89  ! CHECK-DAG: fir.load %arg3 :
90  ! CHECK: %[[r7:.*]] = arith.subi %{{.*}}, %{{.*}} :
91  ! CHECK: %[[s7:.*]] = arith.muli %[[v7]], %[[r7]] :
92  ! CHECK: %[[t7:.*]] = arith.addi %[[s7]], %[[w7]] :
93  ! CHECK: fir.coordinate_of %[[a7]], %[[t7]] :
94  ! CHECK-LABEL: EndIoStatement
95  print *, a7(kk, jj, ii)
96
97end subroutine s
98
99! CHECK-LABEL range
100subroutine range()
101  ! Compile-time initalized arrays
102  integer, dimension(10) :: a0
103  real, dimension(2,3) ::  a1
104  integer, dimension(3,4) :: a2
105  integer, dimension(2,3,4) :: a3
106  complex, dimension(2,3) :: c0, c1
107
108  a0 = (/1, 2, 3, 3, 3, 3, 3, 3, 3, 3/)
109  a1 = reshape((/3.5, 3.5, 3.5, 3.5, 3.5, 3.5/), shape(a1))
110  a2 = reshape((/1, 3, 3, 5, 3, 3, 3, 3, 9, 9, 9, 8/), shape(a2))
111  a3 = reshape((/1, 1, 2, 2, 3, 3, 4, 4, 5, 5, 6, 6, 7, 7, 8, 8, 9, 9, 10, 10, 11, 11, 12, 12/), shape(a3))
112
113  c0 = reshape((/(1.0, 1.5), (2.0, 2.5), (3.0, 3.5), (4.0, 4.5), (5.0, 5.5), (6.0, 6.5)/), shape(c0))
114  data c1/6 * (0.0, 0.0)/
115end subroutine range
116
117! c1 data
118! CHECK: fir.global internal @_QFrangeEc1(dense<(0.000000e+00,0.000000e+00)> : tensor<3x2xcomplex<f32>>) : !fir.array<2x3xcomplex<f32>>
119
120! a0 array constructor
121! CHECK: fir.global internal @_QQro.10xi4.{{.*}}(dense<[1, 2, 3, 3, 3, 3, 3, 3, 3, 3]> : tensor<10xi32>) constant : !fir.array<10xi32>
122
123! a1 array constructor
124! CHECK: fir.global internal @_QQro.2x3xr4.{{.*}}(dense<3.500000e+00> : tensor<3x2xf32>) constant : !fir.array<2x3xf32>
125
126! a2 array constructor
127! CHECK: fir.global internal @_QQro.3x4xi4.{{.*}}(dense<{{\[\[1, 3, 3], \[5, 3, 3], \[3, 3, 9], \[9, 9, 8]]}}> : tensor<4x3xi32>) constant : !fir.array<3x4xi32>
128
129! a3 array constructor
130! CHECK: fir.global internal @_QQro.2x3x4xi4.{{.*}}(dense<{{\[\[\[1, 1], \[2, 2], \[3, 3]], \[\[4, 4], \[5, 5], \[6, 6]], \[\[7, 7], \[8, 8], \[9, 9]], \[\[10, 10], \[11, 11], \[12, 12]]]}}> : tensor<4x3x2xi32>) constant : !fir.array<2x3x4xi32>
131
132! c0 array constructor
133! CHECK: fir.global internal @_QQro.2x3xz4.{{.*}}(dense<{{\[}}[(1.000000e+00,1.500000e+00), (2.000000e+00,2.500000e+00)], [(3.000000e+00,3.500000e+00), (4.000000e+00,4.500000e+00)], [(5.000000e+00,5.500000e+00), (6.000000e+00,6.500000e+00)]]> : tensor<3x2xcomplex<f32>>) constant : !fir.array<2x3xcomplex<f32>>
134
135! CHECK-LABEL rangeGlobal
136subroutine rangeGlobal()
137! CHECK: fir.global internal @_QFrangeglobal{{.*}}(dense<[1, 1, 2, 2, 3, 3]> : tensor<6xi32>) : !fir.array<6xi32>
138  integer, dimension(6) :: a0 = (/ 1, 1, 2, 2, 3, 3 /)
139
140end subroutine rangeGlobal
141
142! CHECK-LABEL hugeGlobal
143subroutine hugeGlobal()
144  integer, parameter :: D = 500
145  integer, dimension(D, D) :: a
146
147! CHECK: fir.global internal @_QQro.500x500xi4.{{.*}}(dense<{{.*}}> : tensor<500x500xi32>) constant : !fir.array<500x500xi32>
148  a = reshape((/(i, i = 1, D * D)/), shape(a))
149end subroutine hugeGlobal
150
151block data
152  real(selected_real_kind(6)) :: x(5,5)
153  common /block/ x
154  data x(1,1), x(2,1), x(3,1) / 1, 1, 0 /
155  data x(1,2), x(2,2), x(4,2) / 1, 1, 2.4 /
156  data x(1,3), x(2,3), x(4,3) / 1, 1, 2.4 /
157  data x(4,4) / 2.4 /
158end
159