aboutsummaryrefslogtreecommitdiffstats
path: root/gcc-4.9/gcc/testsuite/gfortran.dg/intrinsic_spread_1.f90
blob: 04e4c577ac62857efd748a47c73e8fb3c6339ece (plain)
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
145
146
147
148
149
150
151
152
153
154
155
156
157
158
159
160
161
162
163
164
165
166
167
168
169
170
171
172
173
174
175
176
177
178
179
180
181
182
183
184
185
! { dg-do run }
program foo
   implicit none
   integer(kind=1), dimension (10) :: i_1
   integer(kind=1), dimension (2, 3) :: a_1
   integer(kind=1), dimension (2, 2, 3) :: b_1
   integer(kind=2), dimension (10) :: i_2
   integer(kind=2), dimension (2, 3) :: a_2
   integer(kind=2), dimension (2, 2, 3) :: b_2
   integer(kind=4), dimension (10) :: i_4
   integer(kind=4), dimension (2, 3) :: a_4
   integer(kind=4), dimension (2, 2, 3) :: b_4
   integer(kind=8), dimension (10) :: i_8
   integer(kind=8), dimension (2, 3) :: a_8
   integer(kind=8), dimension (2, 2, 3) :: b_8
   real(kind=4), dimension (10) :: r_4
   real(kind=4), dimension (2, 3) :: ar_4
   real(kind=4), dimension (2, 2, 3) :: br_4
   real(kind=8), dimension (10) :: r_8
   real(kind=8), dimension (2, 3) :: ar_8
   real(kind=8), dimension (2, 2, 3) :: br_8
   complex(kind=4), dimension (10) :: c_4
   complex(kind=4), dimension (2, 3) :: ac_4
   complex(kind=4), dimension (2, 2, 3) :: bc_4
   complex(kind=8), dimension (10) :: c_8
   complex(kind=8), dimension (2, 3) :: ac_8
   complex(kind=8), dimension (2, 2, 3) :: bc_8
   type i4_t
      integer(kind=4) :: v
   end type i4_t
   type(i4_t), dimension (10) :: it_4
   type(i4_t), dimension (2, 3) :: at_4
   type(i4_t), dimension (2, 2, 3) :: bt_4
   type(i4_t) :: iv_4

   character (len=200) line1, line2, line3

   a_1 = reshape ((/1_1, 2_1, 3_1, 4_1, 5_1, 6_1/), (/2, 3/))
   b_1 = spread (a_1, 1, 2)
   if (any (b_1 .ne. reshape ((/1_1, 1_1, 2_1, 2_1, 3_1, 3_1, 4_1, 4_1, 5_1, 5_1, 6_1, 6_1/), &
                            (/2, 2, 3/)))) &
      call abort
   line1 = ' '
   write(line1, 9000) b_1
   line2 = ' '
   write(line2, 9000) spread (a_1, 1, 2)
   if (line1 /= line2) call abort
   line3 = ' '
   write(line3, 9000) spread (a_1, 1, 2) + 0_1
   if (line1 /= line3) call abort
   i_1 = spread(1_1,1,10)
   if (any(i_1 /= 1_1)) call abort

   a_2 = reshape ((/1_2, 2_2, 3_2, 4_2, 5_2, 6_2/), (/2, 3/))
   b_2 = spread (a_2, 1, 2)
   if (any (b_2 .ne. reshape ((/1_2, 1_2, 2_2, 2_2, 3_2, 3_2, 4_2, 4_2, 5_2, 5_2, 6_2, 6_2/), &
                            (/2, 2, 3/)))) &
      call abort
   line1 = ' '
   write(line1, 9000) b_2
   line2 = ' '
   write(line2, 9000) spread (a_2, 1, 2)
   if (line1 /= line2) call abort
   line3 = ' '
   write(line3, 9000) spread (a_2, 1, 2) + 0_2
   if (line1 /= line3) call abort
   i_2 = spread(1_2,1,10)
   if (any(i_2 /= 1_2)) call abort

   a_4 = reshape ((/1_4, 2_4, 3_4, 4_4, 5_4, 6_4/), (/2, 3/))
   b_4 = spread (a_4, 1, 2)
   if (any (b_4 .ne. reshape ((/1_4, 1_4, 2_4, 2_4, 3_4, 3_4, 4_4, 4_4, 5_4, 5_4, 6_4, 6_4/), &
                            (/2, 2, 3/)))) &
      call abort
   line1 = ' '
   write(line1, 9000) b_4
   line2 = ' '
   write(line2, 9000) spread (a_4, 1, 2)
   if (line1 /= line2) call abort
   line3 = ' '
   write(line3, 9000) spread (a_4, 1, 2) + 0_4
   if (line1 /= line3) call abort
   i_4 = spread(1_4,1,10)
   if (any(i_4 /= 1_4)) call abort

   a_8 = reshape ((/1_8, 2_8, 3_8, 4_8, 5_8, 6_8/), (/2, 3/))
   b_8 = spread (a_8, 1, 2)
   if (any (b_8 .ne. reshape ((/1_8, 1_8, 2_8, 2_8, 3_8, 3_8, 4_8, 4_8, 5_8, 5_8, 6_8, 6_8/), &
                            (/2, 2, 3/)))) &
      call abort
   line1 = ' '
   write(line1, 9000) b_8
   line2 = ' '
   write(line2, 9000) spread (a_8, 1, 2)
   if (line1 /= line2) call abort
   line3 = ' '
   write(line3, 9000) spread (a_8, 1, 2) + 0_8
   if (line1 /= line3) call abort
   i_8 = spread(1_8,1,10)
   if (any(i_8 /= 1_8)) call abort


   ar_4 = reshape ((/1._4, 2._4, 3._4, 4._4, 5._4, 6._4/), (/2, 3/))
   br_4 = spread (ar_4, 1, 2)
   if (any (br_4 .ne. reshape ((/1._4, 1._4, 2._4, 2._4, 3._4, 3._4, &
   & 4._4, 4._4, 5._4, 5._4, 6._4, 6._4/), (/2, 2, 3/)))) call abort
   line1 = ' '
   write(line1, 9010) br_4
   line2 = ' '
   write(line2, 9010) spread (ar_4, 1, 2)
   if (line1 /= line2) call abort
   line3 = ' '
   write(line3, 9010) spread (ar_4, 1, 2) + 0._4
   if (line1 /= line3) call abort
   r_4 = spread(1._4,1,10)
   if (any(r_4 /= 1._4)) call abort


   ar_8 = reshape ((/1._8, 2._8, 3._8, 4._8, 5._8, 6._8/), (/2, 3/))
   br_8 = spread (ar_8, 1, 2)
   if (any (br_8 .ne. reshape ((/1._8, 1._8, 2._8, 2._8, 3._8, 3._8, &
   & 4._8, 4._8, 5._8, 5._8, 6._8, 6._8/), (/2, 2, 3/)))) call abort
   line1 = ' '
   write(line1, 9010) br_8
   line2 = ' '
   write(line2, 9010) spread (ar_8, 1, 2)
   if (line1 /= line2) call abort
   line3 = ' '
   write(line3, 9010) spread (ar_8, 1, 2) + 0._8
   if (line1 /= line3) call abort
   r_8 = spread(1._8,1,10)
   if (any(r_8 /= 1._8)) call abort

   ac_4 = reshape ((/(1._4,-1._4), (2._4,-2._4), (3._4, -3._4), (4._4, -4._4), &
                   & (5._4,-5._4), (6._4,-6._4)/), (/2, 3/))
   bc_4 = spread (ac_4, 1, 2)
   if (any (real(bc_4) .ne. reshape ((/1._4, 1._4, 2._4, 2._4, 3._4, 3._4, &
   & 4._4, 4._4, 5._4, 5._4, 6._4, 6._4/), (/2, 2, 3/)))) call abort
   if (any (-aimag(bc_4) .ne. reshape ((/1._4, 1._4, 2._4, 2._4, 3._4, 3._4, &
   & 4._4, 4._4, 5._4, 5._4, 6._4, 6._4/), (/2, 2, 3/)))) call abort
   line1 = ' '
   write(line1, 9020) bc_4
   line2 = ' '
   write(line2, 9020) spread (ac_4, 1, 2)
   if (line1 /= line2) call abort
   line3 = ' '
   write(line3, 9020) spread (ac_4, 1, 2) + 0._4
   if (line1 /= line3) call abort
   c_4 = spread((1._4,-1._4),1,10)
   if (any(c_4 /= (1._4,-1._4))) call abort

   ac_8 = reshape ((/(1._8,-1._8), (2._8,-2._8), (3._8, -3._8), (4._8, -4._8), &
                   & (5._8,-5._8), (6._8,-6._8)/), (/2, 3/))
   bc_8 = spread (ac_8, 1, 2)
   if (any (real(bc_8) .ne. reshape ((/1._8, 1._8, 2._8, 2._8, 3._8, 3._8, &
   & 4._8, 4._8, 5._8, 5._8, 6._8, 6._8/), (/2, 2, 3/)))) call abort
   if (any (-aimag(bc_8) .ne. reshape ((/1._8, 1._8, 2._8, 2._8, 3._8, 3._8, &
   & 4._8, 4._8, 5._8, 5._8, 6._8, 6._8/), (/2, 2, 3/)))) call abort
   line1 = ' '
   write(line1, 9020) bc_8
   line2 = ' '
   write(line2, 9020) spread (ac_8, 1, 2)
   if (line1 /= line2) call abort
   line3 = ' '
   write(line3, 9020) spread (ac_8, 1, 2) + 0._8
   if (line1 /= line3) call abort
   c_8 = spread((1._8,-1._8),1,10)
   if (any(c_8 /= (1._8,-1._8))) call abort


   at_4%v = reshape ((/1_4, 2_4, 3_4, 4_4, 5_4, 6_4/), (/2, 3/))
   bt_4 = spread (at_4, 1, 2)
   if (any (bt_4%v .ne. reshape ((/1_4, 1_4, 2_4, 2_4, 3_4, 3_4, 4_4, &
        & 4_4, 5_4, 5_4, 6_4, 6_4/), (/2, 2, 3/)))) &
      call abort
   iv_4%v = 123_4
   it_4 = spread(iv_4,1,10)
   if (any(it_4%v /= 123_4)) call abort


9000 format(12I3)
9010 format(12F7.3)
9020 format(25F7.3)

end program