OpenCores
URL https://opencores.org/ocsvn/openrisc/openrisc/trunk

Subversion Repositories openrisc

[/] [openrisc/] [trunk/] [gnu-dev/] [or1k-gcc/] [gcc/] [testsuite/] [gfortran.dg/] [bound_2.f90] - Blame information for rev 749

Go to most recent revision | Details | Compare with Previous | View Log

Line No. Rev Author Line
1 694 jeremybenn
! { dg-do run }
2
! { dg-options "-std=gnu" }
3
! PR fortran/29391
4
! This file is here to check that LBOUND and UBOUND return correct values
5
!
6
! Contributed by Francois-Xavier Coudert (coudert@clipper.ens.fr)
7
  implicit none
8
  integer :: i(-1:1,-1:1) = 0
9
  integer :: j(-1:2) = 0
10
  integer :: u(7,4,2,9)
11
 
12
  call foo(u,4)
13
  call jackal(-1,-8)
14
  call jackal(-1,8)
15
 
16
  if (any(lbound(i(-1:1,-1:1)) /= 1)) call abort
17
  if (lbound(i(-1:1,-1:1), 1) /= 1) call abort
18
  if (lbound(i(-1:1,-1:1), 2) /= 1) call abort
19
 
20
  if (any(ubound(i(-1:1,-1:1)) /= 3)) call abort
21
  if (ubound(i(-1:1,-1:1), 1) /= 3) call abort
22
  if (ubound(i(-1:1,-1:1), 2) /= 3) call abort
23
 
24
  if (any(lbound(i(:,:)) /= 1)) call abort
25
  if (lbound(i(:,:), 1) /= 1) call abort
26
  if (lbound(i(:,:), 2) /= 1) call abort
27
 
28
  if (any(ubound(i(:,:)) /= 3)) call abort
29
  if (ubound(i(:,:), 1) /= 3) call abort
30
  if (ubound(i(:,:), 2) /= 3) call abort
31
 
32
  if (any(lbound(i(0:,-1:)) /= 1)) call abort
33
  if (lbound(i(0:,-1:), 1) /= 1) call abort
34
  if (lbound(i(0:,-1:), 2) /= 1) call abort
35
 
36
  if (any(ubound(i(0:,-1:)) /= [2,3])) call abort
37
  if (ubound(i(0:,-1:), 1) /= 2) call abort
38
  if (ubound(i(0:,-1:), 2) /= 3) call abort
39
 
40
  if (any(lbound(i(:0,:0)) /= 1)) call abort
41
  if (lbound(i(:0,:0), 1) /= 1) call abort
42
  if (lbound(i(:0,:0), 2) /= 1) call abort
43
 
44
  if (any(ubound(i(:0,:0)) /= 2)) call abort
45
  if (ubound(i(:0,:0), 1) /= 2) call abort
46
  if (ubound(i(:0,:0), 2) /= 2) call abort
47
 
48
  if (any(lbound(transpose(i)) /= 1)) call abort
49
  if (lbound(transpose(i), 1) /= 1) call abort
50
  if (lbound(transpose(i), 2) /= 1) call abort
51
 
52
  if (any(ubound(transpose(i)) /= 3)) call abort
53
  if (ubound(transpose(i), 1) /= 3) call abort
54
  if (ubound(transpose(i), 2) /= 3) call abort
55
 
56
  if (any(lbound(reshape(i,[2,2])) /= 1)) call abort
57
  if (lbound(reshape(i,[2,2]), 1) /= 1) call abort
58
  if (lbound(reshape(i,[2,2]), 2) /= 1) call abort
59
 
60
  if (any(ubound(reshape(i,[2,2])) /= 2)) call abort
61
  if (ubound(reshape(i,[2,2]), 1) /= 2) call abort
62
  if (ubound(reshape(i,[2,2]), 2) /= 2) call abort
63
 
64
  if (any(lbound(cshift(i,-1)) /= 1)) call abort
65
  if (lbound(cshift(i,-1), 1) /= 1) call abort
66
  if (lbound(cshift(i,-1), 2) /= 1) call abort
67
 
68
  if (any(ubound(cshift(i,-1)) /= 3)) call abort
69
  if (ubound(cshift(i,-1), 1) /= 3) call abort
70
  if (ubound(cshift(i,-1), 2) /= 3) call abort
71
 
72
  if (any(lbound(eoshift(i,-1)) /= 1)) call abort
73
  if (lbound(eoshift(i,-1), 1) /= 1) call abort
74
  if (lbound(eoshift(i,-1), 2) /= 1) call abort
75
 
76
  if (any(ubound(eoshift(i,-1)) /= 3)) call abort
77
  if (ubound(eoshift(i,-1), 1) /= 3) call abort
78
  if (ubound(eoshift(i,-1), 2) /= 3) call abort
79
 
80
  if (any(lbound(spread(i,1,2)) /= 1)) call abort
81
  if (lbound(spread(i,1,2), 1) /= 1) call abort
82
  if (lbound(spread(i,1,2), 2) /= 1) call abort
83
 
84
  if (any(ubound(spread(i,1,2)) /= [2,3,3])) call abort
85
  if (ubound(spread(i,1,2), 1) /= 2) call abort
86
  if (ubound(spread(i,1,2), 2) /= 3) call abort
87
  if (ubound(spread(i,1,2), 3) /= 3) call abort
88
 
89
  if (any(lbound(maxloc(i)) /= 1)) call abort
90
  if (lbound(maxloc(i), 1) /= 1) call abort
91
 
92
  if (any(ubound(maxloc(i)) /= 2)) call abort
93
  if (ubound(maxloc(i), 1) /= 2) call abort
94
 
95
  if (any(lbound(minloc(i)) /= 1)) call abort
96
  if (lbound(minloc(i), 1) /= 1) call abort
97
 
98
  if (any(ubound(minloc(i)) /= 2)) call abort
99
  if (ubound(minloc(i), 1) /= 2) call abort
100
 
101
  if (any(lbound(maxval(i,2)) /= 1)) call abort
102
  if (lbound(maxval(i,2), 1) /= 1) call abort
103
 
104
  if (any(ubound(maxval(i,2)) /= 3)) call abort
105
  if (ubound(maxval(i,2), 1) /= 3) call abort
106
 
107
  if (any(lbound(minval(i,2)) /= 1)) call abort
108
  if (lbound(minval(i,2), 1) /= 1) call abort
109
 
110
  if (any(ubound(minval(i,2)) /= 3)) call abort
111
  if (ubound(minval(i,2), 1) /= 3) call abort
112
 
113
  if (any(lbound(any(i==1,2)) /= 1)) call abort
114
  if (lbound(any(i==1,2), 1) /= 1) call abort
115
 
116
  if (any(ubound(any(i==1,2)) /= 3)) call abort
117
  if (ubound(any(i==1,2), 1) /= 3) call abort
118
 
119
  if (any(lbound(count(i==1,2)) /= 1)) call abort
120
  if (lbound(count(i==1,2), 1) /= 1) call abort
121
 
122
  if (any(ubound(count(i==1,2)) /= 3)) call abort
123
  if (ubound(count(i==1,2), 1) /= 3) call abort
124
 
125
  if (any(lbound(merge(i,i,.true.)) /= 1)) call abort
126
  if (lbound(merge(i,i,.true.), 1) /= 1) call abort
127
  if (lbound(merge(i,i,.true.), 2) /= 1) call abort
128
 
129
  if (any(ubound(merge(i,i,.true.)) /= 3)) call abort
130
  if (ubound(merge(i,i,.true.), 1) /= 3) call abort
131
  if (ubound(merge(i,i,.true.), 2) /= 3) call abort
132
 
133
  if (any(lbound(lbound(i)) /= 1)) call abort
134
  if (lbound(lbound(i), 1) /= 1) call abort
135
 
136
  if (any(ubound(lbound(i)) /= 2)) call abort
137
  if (ubound(lbound(i), 1) /= 2) call abort
138
 
139
  if (any(lbound(ubound(i)) /= 1)) call abort
140
  if (lbound(ubound(i), 1) /= 1) call abort
141
 
142
  if (any(ubound(ubound(i)) /= 2)) call abort
143
  if (ubound(ubound(i), 1) /= 2) call abort
144
 
145
  if (any(lbound(shape(i)) /= 1)) call abort
146
  if (lbound(shape(i), 1) /= 1) call abort
147
 
148
  if (any(ubound(shape(i)) /= 2)) call abort
149
  if (ubound(shape(i), 1) /= 2) call abort
150
 
151
  if (any(lbound(product(i,2)) /= 1)) call abort
152
  if (any(ubound(product(i,2)) /= 3)) call abort
153
  if (any(lbound(sum(i,2)) /= 1)) call abort
154
  if (any(ubound(sum(i,2)) /= 3)) call abort
155
  if (any(lbound(matmul(i,i)) /= 1)) call abort
156
  if (any(ubound(matmul(i,i)) /= 3)) call abort
157
  if (any(lbound(pack(i,.true.)) /= 1)) call abort
158
  if (any(ubound(pack(i,.true.)) /= 9)) call abort
159
  if (any(lbound(unpack(j,[.true.],[2])) /= 1)) call abort
160
  if (any(ubound(unpack(j,[.true.],[2])) /= 1)) call abort
161
 
162
  call sub1(i,3)
163
  call sub1(reshape([7,9,4,6,7,9],[3,2]),3)
164
  call sub2
165
 
166
contains
167
 
168
  subroutine sub1(a,n)
169
    integer :: n, a(2:n+1,4:*)
170
 
171
    if (any([lbound(a,1), lbound(a,2)] /= [2, 4])) call abort
172
    if (any(lbound(a) /= [2, 4])) call abort
173
  end subroutine sub1
174
 
175
  subroutine sub2
176
    integer :: x(3:2, 1:2)
177
 
178
    if (size(x) /= 0) call abort
179
    if (lbound (x, 1) /= 1 .or. lbound(x, 2) /= 1) call abort
180
    if (any (lbound (x) /= [1, 1])) call abort
181
    if (ubound (x, 1) /= 0 .or. ubound(x, 2) /= 2) call abort
182
    if (any (ubound (x) /= [0, 2])) call abort
183
  end subroutine sub2
184
 
185
  subroutine sub3
186
    integer :: x(4:5, 1:2)
187
 
188
    if (size(x) /= 0) call abort
189
    if (lbound (x, 1) /= 4 .or. lbound(x, 2) /= 1) call abort
190
    if (any (lbound (x) /= [4, 1])) call abort
191
    if (ubound (x, 1) /= 4 .or. ubound(x, 2) /= 2) call abort
192
    if (any (ubound (x) /= [4, 2])) call abort
193
  end subroutine sub3
194
 
195
  subroutine foo (x,n)
196
    integer :: x(7,n,2,*), n
197
 
198
    if (ubound(x,1) /= 7 .or. ubound(x,2) /= 4 .or. ubound(x,3) /= 2) call abort
199
  end subroutine foo
200
 
201
  subroutine jackal (b, c)
202
    integer :: b, c
203
    integer :: soda(b:c, 3:4)
204
 
205
    if (b > c) then
206
      if (size(soda) /= 0) call abort
207
      if (lbound (soda, 1) /= 1 .or. ubound (soda, 1) /= 0) call abort
208
    else
209
      if (size(soda) /= 2*(c-b+1)) call abort
210
      if (lbound (soda, 1) /= b .or. ubound (soda, 1) /= c) call abort
211
    end if
212
 
213
    if (lbound (soda, 2) /= 3 .or. ubound (soda, 2) /= 4) call abort
214
    if (any (lbound (soda) /= [lbound(soda,1), lbound(soda,2)])) call abort
215
    if (any (ubound (soda) /= [ubound(soda,1), ubound(soda,2)])) call abort
216
 
217
  end subroutine jackal
218
 
219
end

powered by: WebSVN 2.1.0

© copyright 1999-2024 OpenCores.org, equivalent to Oliscience, all rights reserved. OpenCores®, registered trademark.