LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
serrst.f
Go to the documentation of this file.
1*> \brief \b SERRST
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE SERRST( PATH, NUNIT )
12*
13* .. Scalar Arguments ..
14* CHARACTER*3 PATH
15* INTEGER NUNIT
16* ..
17*
18*
19*> \par Purpose:
20* =============
21*>
22*> \verbatim
23*>
24*> SERRST tests the error exits for SSYTRD, SSYTD2, SORGTR, SORMTR, SSPTRD,
25*> SOPGTR, SOPMTR, SSTEQR, SSTERF, SSTEBZ, SSTEIN, SPTEQR, SSBTRD,
26*> SSYEV, SSYEVX, SSYEVD, SSBEV, SSBEVX, SSBEVD,
27*> SSPEV, SSPEVX, SSPEVD, SSTEV, SSTEVX, SSTEVD, and SSTEDC.
28*> SSYEVD_2STAGE, SSYEVR_2STAGE, SSYEVX_2STAGE,
29*> SSYEV_2STAGE, SSBEV_2STAGE, SSBEVD_2STAGE,
30*> SSBEVX_2STAGE, SSYTRD_2STAGE, SSYTRD_SY2SB,
31*> SSYTRD_SB2ST
32*> \endverbatim
33*
34* Arguments:
35* ==========
36*
37*> \param[in] PATH
38*> \verbatim
39*> PATH is CHARACTER*3
40*> The LAPACK path name for the routines to be tested.
41*> \endverbatim
42*>
43*> \param[in] NUNIT
44*> \verbatim
45*> NUNIT is INTEGER
46*> The unit number for output.
47*> \endverbatim
48*
49* Authors:
50* ========
51*
52*> \author Univ. of Tennessee
53*> \author Univ. of California Berkeley
54*> \author Univ. of Colorado Denver
55*> \author NAG Ltd.
56*
57*> \ingroup single_eig
58*
59* =====================================================================
60 SUBROUTINE serrst( PATH, NUNIT )
61*
62* -- LAPACK test routine --
63* -- LAPACK is a software package provided by Univ. of Tennessee, --
64* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
65*
66* .. Scalar Arguments ..
67 CHARACTER*3 PATH
68 INTEGER NUNIT
69* ..
70*
71* =====================================================================
72*
73* NMAX has to be at least 3 or LIW may be too small
74* .. Parameters ..
75 INTEGER NMAX, LIW, LW
76 parameter( nmax = 3, liw = 12*nmax, lw = 20*nmax )
77* ..
78* .. Local Scalars ..
79 CHARACTER*2 C2
80 INTEGER I, INFO, J, M, N, NSPLIT, NT
81* ..
82* .. Local Arrays ..
83 INTEGER I1( NMAX ), I2( NMAX ), I3( NMAX ), IW( LIW )
84 REAL A( NMAX, NMAX ), C( NMAX, NMAX ), D( NMAX ),
85 $ E( NMAX ), Q( NMAX, NMAX ), R( NMAX ),
86 $ TAU( NMAX ), W( LW ), X( NMAX ),
87 $ Z( NMAX, NMAX )
88* ..
89* .. External Functions ..
90 LOGICAL LSAMEN
91 EXTERNAL lsamen
92* ..
93* .. External Subroutines ..
94 EXTERNAL chkxer, sopgtr, sopmtr, sorgtr, sormtr, spteqr,
103* ..
104* .. Scalars in Common ..
105 LOGICAL LERR, OK
106 CHARACTER*32 SRNAMT
107 INTEGER INFOT, NOUT
108* ..
109* .. Common blocks ..
110 COMMON / infoc / infot, nout, ok, lerr
111 COMMON / srnamc / srnamt
112* ..
113* .. Intrinsic Functions ..
114 INTRINSIC real
115* ..
116* .. Executable Statements ..
117*
118 nout = nunit
119 WRITE( nout, fmt = * )
120 c2 = path( 2: 3 )
121*
122* Set the variables to innocuous values.
123*
124 DO 20 j = 1, nmax
125 DO 10 i = 1, nmax
126 a( i, j ) = 1. / real( i+j )
127 10 CONTINUE
128 20 CONTINUE
129 DO 30 j = 1, nmax
130 d( j ) = real( j )
131 e( j ) = 0.0
132 i1( j ) = j
133 i2( j ) = j
134 tau( j ) = 1.
135 30 CONTINUE
136 ok = .true.
137 nt = 0
138*
139* Test error exits for the ST path.
140*
141 IF( lsamen( 2, c2, 'ST' ) ) THEN
142*
143* SSYTRD
144*
145 srnamt = 'SSYTRD'
146 infot = 1
147 CALL ssytrd( '/', 0, a, 1, d, e, tau, w, 1, info )
148 CALL chkxer( 'SSYTRD', infot, nout, lerr, ok )
149 infot = 2
150 CALL ssytrd( 'U', -1, a, 1, d, e, tau, w, 1, info )
151 CALL chkxer( 'SSYTRD', infot, nout, lerr, ok )
152 infot = 4
153 CALL ssytrd( 'U', 2, a, 1, d, e, tau, w, 1, info )
154 CALL chkxer( 'SSYTRD', infot, nout, lerr, ok )
155 infot = 9
156 CALL ssytrd( 'U', 0, a, 1, d, e, tau, w, 0, info )
157 CALL chkxer( 'SSYTRD', infot, nout, lerr, ok )
158 nt = nt + 4
159*
160* SSYTD2
161*
162 srnamt = 'SSYTD2'
163 infot = 1
164 CALL ssytd2( '/', 0, a, 1, d, e, tau, info )
165 CALL chkxer( 'SSYTD2', infot, nout, lerr, ok )
166 infot = 2
167 CALL ssytd2( 'U', -1, a, 1, d, e, tau, info )
168 CALL chkxer( 'SSYTD2', infot, nout, lerr, ok )
169 infot = 4
170 CALL ssytd2( 'U', 2, a, 1, d, e, tau, info )
171 CALL chkxer( 'SSYTD2', infot, nout, lerr, ok )
172 nt = nt + 3
173*
174* SSYTRD_2STAGE
175*
176 srnamt = 'SSYTRD_2STAGE'
177 infot = 1
178 CALL ssytrd_2stage( '/', 'U', 0, a, 1, d, e, tau,
179 $ c, 1, w, 1, info )
180 CALL chkxer( 'SSYTRD_2STAGE', infot, nout, lerr, ok )
181 infot = 1
182 CALL ssytrd_2stage( 'H', 'U', 0, a, 1, d, e, tau,
183 $ c, 1, w, 1, info )
184 CALL chkxer( 'SSYTRD_2STAGE', infot, nout, lerr, ok )
185 infot = 2
186 CALL ssytrd_2stage( 'N', '/', 0, a, 1, d, e, tau,
187 $ c, 1, w, 1, info )
188 CALL chkxer( 'SSYTRD_2STAGE', infot, nout, lerr, ok )
189 infot = 3
190 CALL ssytrd_2stage( 'N', 'U', -1, a, 1, d, e, tau,
191 $ c, 1, w, 1, info )
192 CALL chkxer( 'SSYTRD_2STAGE', infot, nout, lerr, ok )
193 infot = 5
194 CALL ssytrd_2stage( 'N', 'U', 2, a, 1, d, e, tau,
195 $ c, 1, w, 1, info )
196 CALL chkxer( 'SSYTRD_2STAGE', infot, nout, lerr, ok )
197 infot = 10
198 CALL ssytrd_2stage( 'N', 'U', 0, a, 1, d, e, tau,
199 $ c, 0, w, 1, info )
200 CALL chkxer( 'SSYTRD_2STAGE', infot, nout, lerr, ok )
201 infot = 12
202 CALL ssytrd_2stage( 'N', 'U', 0, a, 1, d, e, tau,
203 $ c, 1, w, 0, info )
204 CALL chkxer( 'SSYTRD_2STAGE', infot, nout, lerr, ok )
205 nt = nt + 7
206*
207* SSYTRD_SY2SB
208*
209 srnamt = 'SSYTRD_SY2SB'
210 infot = 1
211 CALL ssytrd_sy2sb( '/', 0, 0, a, 1, c, 1, tau, w, 1, info )
212 CALL chkxer( 'SSYTRD_SY2SB', infot, nout, lerr, ok )
213 infot = 2
214 CALL ssytrd_sy2sb( 'U', -1, 0, a, 1, c, 1, tau, w, 1, info )
215 CALL chkxer( 'SSYTRD_SY2SB', infot, nout, lerr, ok )
216 infot = 3
217 CALL ssytrd_sy2sb( 'U', 0, -1, a, 1, c, 1, tau, w, 1, info )
218 CALL chkxer( 'SSYTRD_SY2SB', infot, nout, lerr, ok )
219 infot = 5
220 CALL ssytrd_sy2sb( 'U', 2, 0, a, 1, c, 1, tau, w, 1, info )
221 CALL chkxer( 'SSYTRD_SY2SB', infot, nout, lerr, ok )
222 infot = 7
223 CALL ssytrd_sy2sb( 'U', 0, 2, a, 1, c, 1, tau, w, 1, info )
224 CALL chkxer( 'SSYTRD_SY2SB', infot, nout, lerr, ok )
225 infot = 10
226 CALL ssytrd_sy2sb( 'U', 0, 0, a, 1, c, 1, tau, w, 0, info )
227 CALL chkxer( 'SSYTRD_SY2SB', infot, nout, lerr, ok )
228 nt = nt + 6
229*
230* SSYTRD_SB2ST
231*
232 srnamt = 'SSYTRD_SB2ST'
233 infot = 1
234 CALL ssytrd_sb2st( '/', 'N', 'U', 0, 0, a, 1, d, e,
235 $ c, 1, w, 1, info )
236 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
237 infot = 2
238 CALL ssytrd_sb2st( 'Y', '/', 'U', 0, 0, a, 1, d, e,
239 $ c, 1, w, 1, info )
240 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
241 infot = 2
242 CALL ssytrd_sb2st( 'Y', 'H', 'U', 0, 0, a, 1, d, e,
243 $ c, 1, w, 1, info )
244 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
245 infot = 3
246 CALL ssytrd_sb2st( 'Y', 'N', '/', 0, 0, a, 1, d, e,
247 $ c, 1, w, 1, info )
248 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
249 infot = 4
250 CALL ssytrd_sb2st( 'Y', 'N', 'U', -1, 0, a, 1, d, e,
251 $ c, 1, w, 1, info )
252 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
253 infot = 5
254 CALL ssytrd_sb2st( 'Y', 'N', 'U', 0, -1, a, 1, d, e,
255 $ c, 1, w, 1, info )
256 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
257 infot = 7
258 CALL ssytrd_sb2st( 'Y', 'N', 'U', 0, 1, a, 1, d, e,
259 $ c, 1, w, 1, info )
260 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
261 infot = 11
262 CALL ssytrd_sb2st( 'Y', 'N', 'U', 0, 0, a, 1, d, e,
263 $ c, 0, w, 1, info )
264 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
265 infot = 13
266 CALL ssytrd_sb2st( 'Y', 'N', 'U', 0, 0, a, 1, d, e,
267 $ c, 1, w, 0, info )
268 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
269 nt = nt + 9
270*
271* SORGTR
272*
273 srnamt = 'SORGTR'
274 infot = 1
275 CALL sorgtr( '/', 0, a, 1, tau, w, 1, info )
276 CALL chkxer( 'SORGTR', infot, nout, lerr, ok )
277 infot = 2
278 CALL sorgtr( 'U', -1, a, 1, tau, w, 1, info )
279 CALL chkxer( 'SORGTR', infot, nout, lerr, ok )
280 infot = 4
281 CALL sorgtr( 'U', 2, a, 1, tau, w, 1, info )
282 CALL chkxer( 'SORGTR', infot, nout, lerr, ok )
283 infot = 7
284 CALL sorgtr( 'U', 3, a, 3, tau, w, 1, info )
285 CALL chkxer( 'SORGTR', infot, nout, lerr, ok )
286 nt = nt + 4
287*
288* SORMTR
289*
290 srnamt = 'SORMTR'
291 infot = 1
292 CALL sormtr( '/', 'U', 'N', 0, 0, a, 1, tau, c, 1, w, 1, info )
293 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
294 infot = 2
295 CALL sormtr( 'L', '/', 'N', 0, 0, a, 1, tau, c, 1, w, 1, info )
296 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
297 infot = 3
298 CALL sormtr( 'L', 'U', '/', 0, 0, a, 1, tau, c, 1, w, 1, info )
299 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
300 infot = 4
301 CALL sormtr( 'L', 'U', 'N', -1, 0, a, 1, tau, c, 1, w, 1,
302 $ info )
303 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
304 infot = 5
305 CALL sormtr( 'L', 'U', 'N', 0, -1, a, 1, tau, c, 1, w, 1,
306 $ info )
307 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
308 infot = 7
309 CALL sormtr( 'L', 'U', 'N', 2, 0, a, 1, tau, c, 2, w, 1, info )
310 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
311 infot = 7
312 CALL sormtr( 'R', 'U', 'N', 0, 2, a, 1, tau, c, 1, w, 1, info )
313 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
314 infot = 10
315 CALL sormtr( 'L', 'U', 'N', 2, 0, a, 2, tau, c, 1, w, 1, info )
316 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
317 infot = 12
318 CALL sormtr( 'L', 'U', 'N', 0, 2, a, 1, tau, c, 1, w, 1, info )
319 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
320 infot = 12
321 CALL sormtr( 'R', 'U', 'N', 2, 0, a, 1, tau, c, 2, w, 1, info )
322 CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
323 nt = nt + 10
324*
325* SSPTRD
326*
327 srnamt = 'SSPTRD'
328 infot = 1
329 CALL ssptrd( '/', 0, a, d, e, tau, info )
330 CALL chkxer( 'SSPTRD', infot, nout, lerr, ok )
331 infot = 2
332 CALL ssptrd( 'U', -1, a, d, e, tau, info )
333 CALL chkxer( 'SSPTRD', infot, nout, lerr, ok )
334 nt = nt + 2
335*
336* SOPGTR
337*
338 srnamt = 'SOPGTR'
339 infot = 1
340 CALL sopgtr( '/', 0, a, tau, z, 1, w, info )
341 CALL chkxer( 'SOPGTR', infot, nout, lerr, ok )
342 infot = 2
343 CALL sopgtr( 'U', -1, a, tau, z, 1, w, info )
344 CALL chkxer( 'SOPGTR', infot, nout, lerr, ok )
345 infot = 6
346 CALL sopgtr( 'U', 2, a, tau, z, 1, w, info )
347 CALL chkxer( 'SOPGTR', infot, nout, lerr, ok )
348 nt = nt + 3
349*
350* SOPMTR
351*
352 srnamt = 'SOPMTR'
353 infot = 1
354 CALL sopmtr( '/', 'U', 'N', 0, 0, a, tau, c, 1, w, info )
355 CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
356 infot = 2
357 CALL sopmtr( 'L', '/', 'N', 0, 0, a, tau, c, 1, w, info )
358 CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
359 infot = 3
360 CALL sopmtr( 'L', 'U', '/', 0, 0, a, tau, c, 1, w, info )
361 CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
362 infot = 4
363 CALL sopmtr( 'L', 'U', 'N', -1, 0, a, tau, c, 1, w, info )
364 CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
365 infot = 5
366 CALL sopmtr( 'L', 'U', 'N', 0, -1, a, tau, c, 1, w, info )
367 CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
368 infot = 9
369 CALL sopmtr( 'L', 'U', 'N', 2, 0, a, tau, c, 1, w, info )
370 CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
371 nt = nt + 6
372*
373* SPTEQR
374*
375 srnamt = 'SPTEQR'
376 infot = 1
377 CALL spteqr( '/', 0, d, e, z, 1, w, info )
378 CALL chkxer( 'SPTEQR', infot, nout, lerr, ok )
379 infot = 2
380 CALL spteqr( 'N', -1, d, e, z, 1, w, info )
381 CALL chkxer( 'SPTEQR', infot, nout, lerr, ok )
382 infot = 6
383 CALL spteqr( 'V', 2, d, e, z, 1, w, info )
384 CALL chkxer( 'SPTEQR', infot, nout, lerr, ok )
385 nt = nt + 3
386*
387* SSTEBZ
388*
389 srnamt = 'SSTEBZ'
390 infot = 1
391 CALL sstebz( '/', 'E', 0, 0.0, 1.0, 1, 0, 0.0, d, e, m, nsplit,
392 $ x, i1, i2, w, iw, info )
393 CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
394 infot = 2
395 CALL sstebz( 'A', '/', 0, 0.0, 0.0, 0, 0, 0.0, d, e, m, nsplit,
396 $ x, i1, i2, w, iw, info )
397 CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
398 infot = 3
399 CALL sstebz( 'A', 'E', -1, 0.0, 0.0, 0, 0, 0.0, d, e, m,
400 $ nsplit, x, i1, i2, w, iw, info )
401 CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
402 infot = 5
403 CALL sstebz( 'V', 'E', 0, 0.0, 0.0, 0, 0, 0.0, d, e, m, nsplit,
404 $ x, i1, i2, w, iw, info )
405 CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
406 infot = 6
407 CALL sstebz( 'I', 'E', 0, 0.0, 0.0, 0, 0, 0.0, d, e, m, nsplit,
408 $ x, i1, i2, w, iw, info )
409 CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
410 infot = 6
411 CALL sstebz( 'I', 'E', 1, 0.0, 0.0, 2, 1, 0.0, d, e, m, nsplit,
412 $ x, i1, i2, w, iw, info )
413 CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
414 infot = 7
415 CALL sstebz( 'I', 'E', 1, 0.0, 0.0, 1, 0, 0.0, d, e, m, nsplit,
416 $ x, i1, i2, w, iw, info )
417 CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
418 infot = 7
419 CALL sstebz( 'I', 'E', 1, 0.0, 0.0, 1, 2, 0.0, d, e, m, nsplit,
420 $ x, i1, i2, w, iw, info )
421 CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
422 nt = nt + 8
423*
424* SSTEIN
425*
426 srnamt = 'SSTEIN'
427 infot = 1
428 CALL sstein( -1, d, e, 0, x, i1, i2, z, 1, w, iw, i3, info )
429 CALL chkxer( 'SSTEIN', infot, nout, lerr, ok )
430 infot = 4
431 CALL sstein( 0, d, e, -1, x, i1, i2, z, 1, w, iw, i3, info )
432 CALL chkxer( 'SSTEIN', infot, nout, lerr, ok )
433 infot = 4
434 CALL sstein( 0, d, e, 1, x, i1, i2, z, 1, w, iw, i3, info )
435 CALL chkxer( 'SSTEIN', infot, nout, lerr, ok )
436 infot = 9
437 CALL sstein( 2, d, e, 0, x, i1, i2, z, 1, w, iw, i3, info )
438 CALL chkxer( 'SSTEIN', infot, nout, lerr, ok )
439 nt = nt + 4
440*
441* SSTEQR
442*
443 srnamt = 'SSTEQR'
444 infot = 1
445 CALL ssteqr( '/', 0, d, e, z, 1, w, info )
446 CALL chkxer( 'SSTEQR', infot, nout, lerr, ok )
447 infot = 2
448 CALL ssteqr( 'N', -1, d, e, z, 1, w, info )
449 CALL chkxer( 'SSTEQR', infot, nout, lerr, ok )
450 infot = 6
451 CALL ssteqr( 'V', 2, d, e, z, 1, w, info )
452 CALL chkxer( 'SSTEQR', infot, nout, lerr, ok )
453 nt = nt + 3
454*
455* SSTERF
456*
457 srnamt = 'SSTERF'
458 infot = 1
459 CALL ssterf( -1, d, e, info )
460 CALL chkxer( 'SSTERF', infot, nout, lerr, ok )
461 nt = nt + 1
462*
463* SSTEDC
464*
465 srnamt = 'SSTEDC'
466 infot = 1
467 CALL sstedc( '/', 0, d, e, z, 1, w, 1, iw, 1, info )
468 CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
469 infot = 2
470 CALL sstedc( 'N', -1, d, e, z, 1, w, 1, iw, 1, info )
471 CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
472 infot = 6
473 CALL sstedc( 'V', 2, d, e, z, 1, w, 23, iw, 28, info )
474 CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
475 infot = 8
476 CALL sstedc( 'N', 1, d, e, z, 1, w, 0, iw, 1, info )
477 CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
478 infot = 8
479 CALL sstedc( 'I', 2, d, e, z, 2, w, 0, iw, 12, info )
480 CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
481 infot = 8
482 CALL sstedc( 'V', 2, d, e, z, 2, w, 0, iw, 28, info )
483 CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
484 infot = 10
485 CALL sstedc( 'N', 1, d, e, z, 1, w, 1, iw, 0, info )
486 CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
487 infot = 10
488 CALL sstedc( 'I', 2, d, e, z, 2, w, 19, iw, 0, info )
489 CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
490 infot = 10
491 CALL sstedc( 'V', 2, d, e, z, 2, w, 23, iw, 0, info )
492 CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
493 nt = nt + 9
494*
495* SSTEVD
496*
497 srnamt = 'SSTEVD'
498 infot = 1
499 CALL sstevd( '/', 0, d, e, z, 1, w, 1, iw, 1, info )
500 CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
501 infot = 2
502 CALL sstevd( 'N', -1, d, e, z, 1, w, 1, iw, 1, info )
503 CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
504 infot = 6
505 CALL sstevd( 'V', 2, d, e, z, 1, w, 19, iw, 12, info )
506 CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
507 infot = 8
508 CALL sstevd( 'N', 1, d, e, z, 1, w, 0, iw, 1, info )
509 CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
510 infot = 8
511 CALL sstevd( 'V', 2, d, e, z, 2, w, 12, iw, 12, info )
512 CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
513 infot = 10
514 CALL sstevd( 'N', 0, d, e, z, 1, w, 1, iw, 0, info )
515 CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
516 infot = 10
517 CALL sstevd( 'V', 2, d, e, z, 2, w, 19, iw, 11, info )
518 CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
519 nt = nt + 7
520*
521* SSTEV
522*
523 srnamt = 'SSTEV '
524 infot = 1
525 CALL sstev( '/', 0, d, e, z, 1, w, info )
526 CALL chkxer( 'SSTEV ', infot, nout, lerr, ok )
527 infot = 2
528 CALL sstev( 'N', -1, d, e, z, 1, w, info )
529 CALL chkxer( 'SSTEV ', infot, nout, lerr, ok )
530 infot = 6
531 CALL sstev( 'V', 2, d, e, z, 1, w, info )
532 CALL chkxer( 'SSTEV ', infot, nout, lerr, ok )
533 nt = nt + 3
534*
535* SSTEVX
536*
537 srnamt = 'SSTEVX'
538 infot = 1
539 CALL sstevx( '/', 'A', 0, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
540 $ 1, w, iw, i3, info )
541 CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
542 infot = 2
543 CALL sstevx( 'N', '/', 0, d, e, 0.0, 1.0, 1, 0, 0.0, m, x, z,
544 $ 1, w, iw, i3, info )
545 CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
546 infot = 3
547 CALL sstevx( 'N', 'A', -1, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
548 $ 1, w, iw, i3, info )
549 CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
550 infot = 7
551 CALL sstevx( 'N', 'V', 1, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
552 $ 1, w, iw, i3, info )
553 CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
554 infot = 8
555 CALL sstevx( 'N', 'I', 1, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
556 $ 1, w, iw, i3, info )
557 CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
558 infot = 8
559 CALL sstevx( 'N', 'I', 1, d, e, 0.0, 0.0, 2, 1, 0.0, m, x, z,
560 $ 1, w, iw, i3, info )
561 CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
562 infot = 9
563 CALL sstevx( 'N', 'I', 2, d, e, 0.0, 0.0, 2, 1, 0.0, m, x, z,
564 $ 1, w, iw, i3, info )
565 CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
566 infot = 9
567 CALL sstevx( 'N', 'I', 1, d, e, 0.0, 0.0, 1, 2, 0.0, m, x, z,
568 $ 1, w, iw, i3, info )
569 CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
570 infot = 14
571 CALL sstevx( 'V', 'A', 2, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
572 $ 1, w, iw, i3, info )
573 CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
574 nt = nt + 9
575*
576* SSTEVR
577*
578 n = 1
579 srnamt = 'SSTEVR'
580 infot = 1
581 CALL sstevr( '/', 'A', 0, d, e, 0.0, 0.0, 1, 1, 0.0, m, r, z,
582 $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
583 CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
584 infot = 2
585 CALL sstevr( 'V', '/', 0, d, e, 0.0, 0.0, 1, 1, 0.0, m, r, z,
586 $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
587 CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
588 infot = 3
589 CALL sstevr( 'V', 'A', -1, d, e, 0.0, 0.0, 1, 1, 0.0, m, r, z,
590 $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
591 CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
592 infot = 7
593 CALL sstevr( 'V', 'V', 1, d, e, 0.0, 0.0, 1, 1, 0.0, m, r, z,
594 $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
595 CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
596 infot = 8
597 CALL sstevr( 'V', 'I', 1, d, e, 0.0, 0.0, 0, 1, 0.0, m, w, z,
598 $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
599 CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
600 infot = 9
601 n = 2
602 CALL sstevr( 'V', 'I', 2, d, e, 0.0, 0.0, 2, 1, 0.0, m, w, z,
603 $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
604 CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
605 infot = 14
606 n = 1
607 CALL sstevr( 'V', 'I', 1, d, e, 0.0, 0.0, 1, 1, 0.0, m, w, z,
608 $ 0, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
609 CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
610 infot = 17
611 CALL sstevr( 'V', 'I', 1, d, e, 0.0, 0.0, 1, 1, 0.0, m, w, z,
612 $ 1, iw, x, 20*n-1, iw( 2*n+1 ), 10*n, info )
613 CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
614 infot = 19
615 CALL sstevr( 'V', 'I', 1, d, e, 0.0, 0.0, 1, 1, 0.0, m, w, z,
616 $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n-1, info )
617 CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
618 nt = nt + 9
619*
620* SSYEVD
621*
622 srnamt = 'SSYEVD'
623 infot = 1
624 CALL ssyevd( '/', 'U', 0, a, 1, x, w, 1, iw, 1, info )
625 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
626 infot = 2
627 CALL ssyevd( 'N', '/', 0, a, 1, x, w, 1, iw, 1, info )
628 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
629 infot = 3
630 CALL ssyevd( 'N', 'U', -1, a, 1, x, w, 1, iw, 1, info )
631 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
632 infot = 5
633 CALL ssyevd( 'N', 'U', 2, a, 1, x, w, 3, iw, 1, info )
634 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
635 infot = 8
636 CALL ssyevd( 'N', 'U', 1, a, 1, x, w, 0, iw, 1, info )
637 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
638 infot = 8
639 CALL ssyevd( 'N', 'U', 2, a, 2, x, w, 4, iw, 1, info )
640 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
641 infot = 8
642 CALL ssyevd( 'V', 'U', 2, a, 2, x, w, 20, iw, 12, info )
643 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
644 infot = 10
645 CALL ssyevd( 'N', 'U', 1, a, 1, x, w, 1, iw, 0, info )
646 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
647 infot = 10
648 CALL ssyevd( 'N', 'U', 2, a, 2, x, w, 5, iw, 0, info )
649 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
650 infot = 10
651 CALL ssyevd( 'V', 'U', 2, a, 2, x, w, 27, iw, 11, info )
652 CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
653 nt = nt + 10
654*
655* SSYEVD_2STAGE
656*
657 srnamt = 'SSYEVD_2STAGE'
658 infot = 1
659 CALL ssyevd_2stage( '/', 'U', 0, a, 1, x, w, 1, iw, 1, info )
660 CALL chkxer( 'SSYEVD_2STAGE', infot, nout, lerr, ok )
661 infot = 1
662 CALL ssyevd_2stage( 'V', 'U', 0, a, 1, x, w, 1, iw, 1, info )
663 CALL chkxer( 'SSYEVD_2STAGE', infot, nout, lerr, ok )
664 infot = 2
665 CALL ssyevd_2stage( 'N', '/', 0, a, 1, x, w, 1, iw, 1, info )
666 CALL chkxer( 'SSYEVD_2STAGE', infot, nout, lerr, ok )
667 infot = 3
668 CALL ssyevd_2stage( 'N', 'U', -1, a, 1, x, w, 1, iw, 1, info )
669 CALL chkxer( 'SSYEVD_2STAGE', infot, nout, lerr, ok )
670 infot = 5
671 CALL ssyevd_2stage( 'N', 'U', 2, a, 1, x, w, 3, iw, 1, info )
672 CALL chkxer( 'SSYEVD_2STAGE', infot, nout, lerr, ok )
673 infot = 8
674 CALL ssyevd_2stage( 'N', 'U', 1, a, 1, x, w, 0, iw, 1, info )
675 CALL chkxer( 'SSYEVD_2STAGE', infot, nout, lerr, ok )
676 infot = 8
677 CALL ssyevd_2stage( 'N', 'U', 2, a, 2, x, w, 4, iw, 1, info )
678 CALL chkxer( 'SSYEVD_2STAGE', infot, nout, lerr, ok )
679* INFOT = 8
680* CALL SSYEVD_2STAGE( 'V', 'U', 2, A, 2, X, W, 20, IW, 12, INFO )
681* CALL CHKXER( 'SSYEVD_2STAGE', INFOT, NOUT, LERR, OK )
682 infot = 10
683 CALL ssyevd_2stage( 'N', 'U', 1, a, 1, x, w, 1, iw, 0, info )
684 CALL chkxer( 'SSYEVD_2STAGE', infot, nout, lerr, ok )
685 infot = 10
686 CALL ssyevd_2stage( 'N', 'U', 2, a, 2, x, w, 25, iw, 0, info )
687 CALL chkxer( 'SSYEVD_2STAGE', infot, nout, lerr, ok )
688* INFOT = 10
689* CALL SSYEVD_2STAGE( 'V', 'U', 2, A, 2, X, W, 27, IW, 11, INFO )
690* CALL CHKXER( 'SSYEVD_2STAGE', INFOT, NOUT, LERR, OK )
691 nt = nt + 9
692*
693* SSYEVR
694*
695 srnamt = 'SSYEVR'
696 n = 1
697 infot = 1
698 CALL ssyevr( '/', 'A', 'U', 0, a, 1, 0.0, 0.0, 1, 1, 0.0, m, r,
699 $ z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
700 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
701 infot = 2
702 CALL ssyevr( 'V', '/', 'U', 0, a, 1, 0.0, 0.0, 1, 1, 0.0, m, r,
703 $ z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
704 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
705 infot = 3
706 CALL ssyevr( 'V', 'A', '/', -1, a, 1, 0.0, 0.0, 1, 1, 0.0, m,
707 $ r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
708 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
709 infot = 4
710 CALL ssyevr( 'V', 'A', 'U', -1, a, 1, 0.0, 0.0, 1, 1, 0.0, m,
711 $ r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
712 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
713 infot = 6
714 CALL ssyevr( 'V', 'A', 'U', 2, a, 1, 0.0, 0.0, 1, 1, 0.0, m, r,
715 $ z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
716 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
717 infot = 8
718 CALL ssyevr( 'V', 'V', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
719 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
720 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
721 infot = 9
722 CALL ssyevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 0, 1, 0.0,
723 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
724 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
725 infot = 10
726*
727 CALL ssyevr( 'V', 'I', 'U', 2, a, 2, 0.0e0, 0.0e0, 2, 1, 0.0,
728 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
729 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
730 infot = 15
731 CALL ssyevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
732 $ m, r, z, 0, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
733 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
734 infot = 18
735 CALL ssyevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
736 $ m, r, z, 1, iw, q, 26*n-1, iw( 2*n+1 ), 10*n,
737 $ info )
738 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
739 infot = 20
740 CALL ssyevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
741 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n-1,
742 $ info )
743 CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
744 nt = nt + 11
745*
746* SSYEVR_2STAGE
747*
748 srnamt = 'SSYEVR_2STAGE'
749 n = 1
750 infot = 1
751 CALL ssyevr_2stage( '/', 'A', 'U', 0, a, 1,
752 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
753 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
754 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
755 infot = 1
756 CALL ssyevr_2stage( 'V', 'A', 'U', 0, a, 1,
757 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
758 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
759 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
760 infot = 2
761 CALL ssyevr_2stage( 'N', '/', 'U', 0, a, 1,
762 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
763 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
764 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
765 infot = 3
766 CALL ssyevr_2stage( 'N', 'A', '/', -1, a, 1,
767 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
768 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
769 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
770 infot = 4
771 CALL ssyevr_2stage( 'N', 'A', 'U', -1, a, 1,
772 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
773 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
774 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
775 infot = 6
776 CALL ssyevr_2stage( 'N', 'A', 'U', 2, a, 1,
777 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
778 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
779 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
780 infot = 8
781 CALL ssyevr_2stage( 'N', 'V', 'U', 1, a, 1,
782 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
783 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
784 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
785 infot = 9
786 CALL ssyevr_2stage( 'N', 'I', 'U', 1, a, 1,
787 $ 0.0e0, 0.0e0, 0, 1, 0.0e0,
788 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
789 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
790 infot = 10
791 CALL ssyevr_2stage( 'N', 'I', 'U', 2, a, 2,
792 $ 0.0e0, 0.0e0, 2, 1, 0.0e0,
793 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
794 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
795 infot = 15
796 CALL ssyevr_2stage( 'N', 'I', 'U', 1, a, 1,
797 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
798 $ m, r, z, 0, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
799 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
800 infot = 18
801 CALL ssyevr_2stage( 'N', 'I', 'U', 1, a, 1,
802 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
803 $ m, r, z, 1, iw, q, 0, iw( 2*n+1 ), 10*n,
804 $ info )
805 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
806 infot = 20
807 CALL ssyevr_2stage( 'N', 'I', 'U', 1, a, 1,
808 $ 0.0e0, 0.0e0, 1, 1, 0.0e0,
809 $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 0,
810 $ info )
811 CALL chkxer( 'SSYEVR_2STAGE', infot, nout, lerr, ok )
812 nt = nt + 12
813*
814* SSYEV
815*
816 srnamt = 'SSYEV '
817 infot = 1
818 CALL ssyev( '/', 'U', 0, a, 1, x, w, 1, info )
819 CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
820 infot = 2
821 CALL ssyev( 'N', '/', 0, a, 1, x, w, 1, info )
822 CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
823 infot = 3
824 CALL ssyev( 'N', 'U', -1, a, 1, x, w, 1, info )
825 CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
826 infot = 5
827 CALL ssyev( 'N', 'U', 2, a, 1, x, w, 3, info )
828 CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
829 infot = 8
830 CALL ssyev( 'N', 'U', 1, a, 1, x, w, 1, info )
831 CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
832 nt = nt + 5
833*
834* SSYEV_2STAGE
835*
836 srnamt = 'SSYEV_2STAGE '
837 infot = 1
838 CALL ssyev_2stage( '/', 'U', 0, a, 1, x, w, 1, info )
839 CALL chkxer( 'SSYEV_2STAGE ', infot, nout, lerr, ok )
840 infot = 1
841 CALL ssyev_2stage( 'V', 'U', 0, a, 1, x, w, 1, info )
842 CALL chkxer( 'SSYEV_2STAGE ', infot, nout, lerr, ok )
843 infot = 2
844 CALL ssyev_2stage( 'N', '/', 0, a, 1, x, w, 1, info )
845 CALL chkxer( 'SSYEV_2STAGE ', infot, nout, lerr, ok )
846 infot = 3
847 CALL ssyev_2stage( 'N', 'U', -1, a, 1, x, w, 1, info )
848 CALL chkxer( 'SSYEV_2STAGE ', infot, nout, lerr, ok )
849 infot = 5
850 CALL ssyev_2stage( 'N', 'U', 2, a, 1, x, w, 3, info )
851 CALL chkxer( 'SSYEV_2STAGE ', infot, nout, lerr, ok )
852 infot = 8
853 CALL ssyev_2stage( 'N', 'U', 1, a, 1, x, w, 1, info )
854 CALL chkxer( 'SSYEV_2STAGE ', infot, nout, lerr, ok )
855 nt = nt + 6
856*
857* SSYEVX
858*
859 srnamt = 'SSYEVX'
860 infot = 1
861 CALL ssyevx( '/', 'A', 'U', 0, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
862 $ z, 1, w, 1, iw, i3, info )
863 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
864 infot = 2
865 CALL ssyevx( 'N', '/', 'U', 0, a, 1, 0.0, 1.0, 1, 0, 0.0, m, x,
866 $ z, 1, w, 1, iw, i3, info )
867 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
868 infot = 3
869 CALL ssyevx( 'N', 'A', '/', 0, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
870 $ z, 1, w, 1, iw, i3, info )
871 infot = 4
872 CALL ssyevx( 'N', 'A', 'U', -1, a, 1, 0.0, 0.0, 0, 0, 0.0, m,
873 $ x, z, 1, w, 1, iw, i3, info )
874 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
875 infot = 6
876 CALL ssyevx( 'N', 'A', 'U', 2, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
877 $ z, 1, w, 16, iw, i3, info )
878 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
879 infot = 8
880 CALL ssyevx( 'N', 'V', 'U', 1, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
881 $ z, 1, w, 8, iw, i3, info )
882 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
883 infot = 9
884 CALL ssyevx( 'N', 'I', 'U', 1, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
885 $ z, 1, w, 8, iw, i3, info )
886 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
887 infot = 9
888 CALL ssyevx( 'N', 'I', 'U', 1, a, 1, 0.0, 0.0, 2, 1, 0.0, m, x,
889 $ z, 1, w, 8, iw, i3, info )
890 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
891 infot = 10
892 CALL ssyevx( 'N', 'I', 'U', 2, a, 2, 0.0, 0.0, 2, 1, 0.0, m, x,
893 $ z, 1, w, 16, iw, i3, info )
894 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
895 infot = 10
896 CALL ssyevx( 'N', 'I', 'U', 1, a, 1, 0.0, 0.0, 1, 2, 0.0, m, x,
897 $ z, 1, w, 8, iw, i3, info )
898 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
899 infot = 15
900 CALL ssyevx( 'V', 'A', 'U', 2, a, 2, 0.0, 0.0, 0, 0, 0.0, m, x,
901 $ z, 1, w, 16, iw, i3, info )
902 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
903 infot = 17
904 CALL ssyevx( 'V', 'A', 'U', 1, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
905 $ z, 1, w, 0, iw, i3, info )
906 CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
907 nt = nt + 12
908*
909* SSYEVX_2STAGE
910*
911 srnamt = 'SSYEVX_2STAGE'
912 infot = 1
913 CALL ssyevx_2stage( '/', 'A', 'U', 0, a, 1,
914 $ 0.0e0, 0.0e0, 0, 0, 0.0e0,
915 $ m, x, z, 1, w, 1, iw, i3, info )
916 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
917 infot = 1
918 CALL ssyevx_2stage( 'V', 'A', 'U', 0, a, 1,
919 $ 0.0e0, 0.0e0, 0, 0, 0.0e0,
920 $ m, x, z, 1, w, 1, iw, i3, info )
921 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
922 infot = 2
923 CALL ssyevx_2stage( 'N', '/', 'U', 0, a, 1,
924 $ 0.0e0, 1.0e0, 1, 0, 0.0e0,
925 $ m, x, z, 1, w, 1, iw, i3, info )
926 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
927 infot = 3
928 CALL ssyevx_2stage( 'N', 'A', '/', 0, a, 1,
929 $ 0.0e0, 0.0e0, 0, 0, 0.0e0,
930 $ m, x, z, 1, w, 1, iw, i3, info )
931 infot = 4
932 CALL ssyevx_2stage( 'N', 'A', 'U', -1, a, 1,
933 $ 0.0e0, 0.0e0, 0, 0, 0.0e0,
934 $ m, x, z, 1, w, 1, iw, i3, info )
935 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
936 infot = 6
937 CALL ssyevx_2stage( 'N', 'A', 'U', 2, a, 1,
938 $ 0.0e0, 0.0e0, 0, 0, 0.0e0,
939 $ m, x, z, 1, w, 16, iw, i3, info )
940 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
941 infot = 8
942 CALL ssyevx_2stage( 'N', 'V', 'U', 1, a, 1,
943 $ 0.0e0, 0.0e0, 0, 0, 0.0e0,
944 $ m, x, z, 1, w, 8, iw, i3, info )
945 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
946 infot = 9
947 CALL ssyevx_2stage( 'N', 'I', 'U', 1, a, 1,
948 $ 0.0e0, 0.0e0, 0, 0, 0.0e0,
949 $ m, x, z, 1, w, 8, iw, i3, info )
950 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
951 infot = 9
952 CALL ssyevx_2stage( 'N', 'I', 'U', 1, a, 1,
953 $ 0.0e0, 0.0e0, 2, 1, 0.0e0,
954 $ m, x, z, 1, w, 8, iw, i3, info )
955 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
956 infot = 10
957 CALL ssyevx_2stage( 'N', 'I', 'U', 2, a, 2,
958 $ 0.0e0, 0.0e0, 2, 1, 0.0e0,
959 $ m, x, z, 1, w, 16, iw, i3, info )
960 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
961 infot = 10
962 CALL ssyevx_2stage( 'N', 'I', 'U', 1, a, 1,
963 $ 0.0e0, 0.0e0, 1, 2, 0.0e0,
964 $ m, x, z, 1, w, 8, iw, i3, info )
965 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
966 infot = 15
967 CALL ssyevx_2stage( 'N', 'A', 'U', 2, a, 2,
968 $ 0.0e0, 0.0e0, 0, 0, 0.0e0,
969 $ m, x, z, 0, w, 16, iw, i3, info )
970 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
971 infot = 17
972 CALL ssyevx_2stage( 'N', 'A', 'U', 1, a, 1,
973 $ 0.0e0, 0.0e0, 0, 0, 0.0e0,
974 $ m, x, z, 1, w, 0, iw, i3, info )
975 CALL chkxer( 'SSYEVX_2STAGE', infot, nout, lerr, ok )
976 nt = nt + 13
977*
978* SSPEVD
979*
980 srnamt = 'SSPEVD'
981 infot = 1
982 CALL sspevd( '/', 'U', 0, a, x, z, 1, w, 1, iw, 1, info )
983 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
984 infot = 2
985 CALL sspevd( 'N', '/', 0, a, x, z, 1, w, 1, iw, 1, info )
986 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
987 infot = 3
988 CALL sspevd( 'N', 'U', -1, a, x, z, 1, w, 1, iw, 1, info )
989 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
990 infot = 7
991 CALL sspevd( 'V', 'U', 2, a, x, z, 1, w, 23, iw, 12, info )
992 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
993 infot = 9
994 CALL sspevd( 'N', 'U', 1, a, x, z, 1, w, 0, iw, 1, info )
995 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
996 infot = 9
997 CALL sspevd( 'N', 'U', 2, a, x, z, 1, w, 3, iw, 1, info )
998 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
999 infot = 9
1000 CALL sspevd( 'V', 'U', 2, a, x, z, 2, w, 16, iw, 12, info )
1001 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
1002 infot = 11
1003 CALL sspevd( 'N', 'U', 1, a, x, z, 1, w, 1, iw, 0, info )
1004 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
1005 infot = 11
1006 CALL sspevd( 'N', 'U', 2, a, x, z, 1, w, 4, iw, 0, info )
1007 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
1008 infot = 11
1009 CALL sspevd( 'V', 'U', 2, a, x, z, 2, w, 23, iw, 11, info )
1010 CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
1011 nt = nt + 10
1012*
1013* SSPEV
1014*
1015 srnamt = 'SSPEV '
1016 infot = 1
1017 CALL sspev( '/', 'U', 0, a, w, z, 1, x, info )
1018 CALL chkxer( 'SSPEV ', infot, nout, lerr, ok )
1019 infot = 2
1020 CALL sspev( 'N', '/', 0, a, w, z, 1, x, info )
1021 CALL chkxer( 'SSPEV ', infot, nout, lerr, ok )
1022 infot = 3
1023 CALL sspev( 'N', 'U', -1, a, w, z, 1, x, info )
1024 CALL chkxer( 'SSPEV ', infot, nout, lerr, ok )
1025 infot = 7
1026 CALL sspev( 'V', 'U', 2, a, w, z, 1, x, info )
1027 CALL chkxer( 'SSPEV ', infot, nout, lerr, ok )
1028 nt = nt + 4
1029*
1030* SSPEVX
1031*
1032 srnamt = 'SSPEVX'
1033 infot = 1
1034 CALL sspevx( '/', 'A', 'U', 0, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
1035 $ 1, w, iw, i3, info )
1036 CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
1037 infot = 2
1038 CALL sspevx( 'N', '/', 'U', 0, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
1039 $ 1, w, iw, i3, info )
1040 CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
1041 infot = 3
1042 CALL sspevx( 'N', 'A', '/', 0, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
1043 $ 1, w, iw, i3, info )
1044 infot = 4
1045 CALL sspevx( 'N', 'A', 'U', -1, a, 0.0, 0.0, 0, 0, 0.0, m, x,
1046 $ z, 1, w, iw, i3, info )
1047 CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
1048 infot = 7
1049 CALL sspevx( 'N', 'V', 'U', 1, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
1050 $ 1, w, iw, i3, info )
1051 CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
1052 infot = 8
1053 CALL sspevx( 'N', 'I', 'U', 1, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
1054 $ 1, w, iw, i3, info )
1055 CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
1056 infot = 8
1057 CALL sspevx( 'N', 'I', 'U', 1, a, 0.0, 0.0, 2, 1, 0.0, m, x, z,
1058 $ 1, w, iw, i3, info )
1059 CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
1060 infot = 9
1061 CALL sspevx( 'N', 'I', 'U', 2, a, 0.0, 0.0, 2, 1, 0.0, m, x, z,
1062 $ 1, w, iw, i3, info )
1063 CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
1064 infot = 9
1065 CALL sspevx( 'N', 'I', 'U', 1, a, 0.0, 0.0, 1, 2, 0.0, m, x, z,
1066 $ 1, w, iw, i3, info )
1067 CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
1068 infot = 14
1069 CALL sspevx( 'V', 'A', 'U', 2, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
1070 $ 1, w, iw, i3, info )
1071 CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
1072 nt = nt + 10
1073*
1074* Test error exits for the SB path.
1075*
1076 ELSE IF( lsamen( 2, c2, 'SB' ) ) THEN
1077*
1078* SSBTRD
1079*
1080 srnamt = 'SSBTRD'
1081 infot = 1
1082 CALL ssbtrd( '/', 'U', 0, 0, a, 1, d, e, z, 1, w, info )
1083 CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
1084 infot = 2
1085 CALL ssbtrd( 'N', '/', 0, 0, a, 1, d, e, z, 1, w, info )
1086 CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
1087 infot = 3
1088 CALL ssbtrd( 'N', 'U', -1, 0, a, 1, d, e, z, 1, w, info )
1089 CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
1090 infot = 4
1091 CALL ssbtrd( 'N', 'U', 0, -1, a, 1, d, e, z, 1, w, info )
1092 CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
1093 infot = 6
1094 CALL ssbtrd( 'N', 'U', 1, 1, a, 1, d, e, z, 1, w, info )
1095 CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
1096 infot = 10
1097 CALL ssbtrd( 'V', 'U', 2, 0, a, 1, d, e, z, 1, w, info )
1098 CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
1099 nt = nt + 6
1100*
1101* SSYTRD_SB2ST
1102*
1103 srnamt = 'SSYTRD_SB2ST'
1104 infot = 1
1105 CALL ssytrd_sb2st( '/', 'N', 'U', 0, 0, a, 1, d, e,
1106 $ c, 1, w, 1, info )
1107 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
1108 infot = 2
1109 CALL ssytrd_sb2st( 'N', '/', 'U', 0, 0, a, 1, d, e,
1110 $ c, 1, w, 1, info )
1111 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
1112 infot = 2
1113 CALL ssytrd_sb2st( 'N', 'H', 'U', 0, 0, a, 1, d, e,
1114 $ c, 1, w, 1, info )
1115 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
1116 infot = 3
1117 CALL ssytrd_sb2st( 'N', 'N', '/', 0, 0, a, 1, d, e,
1118 $ c, 1, w, 1, info )
1119 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
1120 infot = 4
1121 CALL ssytrd_sb2st( 'N', 'N', 'U', -1, 0, a, 1, d, e,
1122 $ c, 1, w, 1, info )
1123 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
1124 infot = 5
1125 CALL ssytrd_sb2st( 'N', 'N', 'U', 0, -1, a, 1, d, e,
1126 $ c, 1, w, 1, info )
1127 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
1128 infot = 7
1129 CALL ssytrd_sb2st( 'N', 'N', 'U', 0, 1, a, 1, d, e,
1130 $ c, 1, w, 1, info )
1131 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
1132 infot = 11
1133 CALL ssytrd_sb2st( 'N', 'N', 'U', 0, 0, a, 1, d, e,
1134 $ c, 0, w, 1, info )
1135 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
1136 infot = 13
1137 CALL ssytrd_sb2st( 'N', 'N', 'U', 0, 0, a, 1, d, e,
1138 $ c, 1, w, 0, info )
1139 CALL chkxer( 'SSYTRD_SB2ST', infot, nout, lerr, ok )
1140 nt = nt + 9
1141*
1142* SSBEVD
1143*
1144 srnamt = 'SSBEVD'
1145 infot = 1
1146 CALL ssbevd( '/', 'U', 0, 0, a, 1, x, z, 1, w, 1, iw, 1, info )
1147 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1148 infot = 2
1149 CALL ssbevd( 'N', '/', 0, 0, a, 1, x, z, 1, w, 1, iw, 1, info )
1150 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1151 infot = 3
1152 CALL ssbevd( 'N', 'U', -1, 0, a, 1, x, z, 1, w, 1, iw, 1,
1153 $ info )
1154 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1155 infot = 4
1156 CALL ssbevd( 'N', 'U', 0, -1, a, 1, x, z, 1, w, 1, iw, 1,
1157 $ info )
1158 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1159 infot = 6
1160 CALL ssbevd( 'N', 'U', 2, 1, a, 1, x, z, 1, w, 4, iw, 1, info )
1161 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1162 infot = 9
1163 CALL ssbevd( 'V', 'U', 2, 1, a, 2, x, z, 1, w, 25, iw, 12,
1164 $ info )
1165 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1166 infot = 11
1167 CALL ssbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 0, iw, 1, info )
1168 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1169 infot = 11
1170 CALL ssbevd( 'N', 'U', 2, 0, a, 1, x, z, 1, w, 3, iw, 1, info )
1171 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1172 infot = 11
1173 CALL ssbevd( 'V', 'U', 2, 0, a, 1, x, z, 2, w, 18, iw, 12,
1174 $ info )
1175 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1176 infot = 13
1177 CALL ssbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 1, iw, 0, info )
1178 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1179 infot = 13
1180 CALL ssbevd( 'V', 'U', 2, 0, a, 1, x, z, 2, w, 25, iw, 11,
1181 $ info )
1182 CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
1183 nt = nt + 11
1184*
1185* SSBEVD_2STAGE
1186*
1187 srnamt = 'SSBEVD_2STAGE'
1188 infot = 1
1189 CALL ssbevd_2stage( '/', 'U', 0, 0, a, 1, x, z, 1, w,
1190 $ 1, iw, 1, info )
1191 CALL chkxer( 'SSBEVD_2STAGE', infot, nout, lerr, ok )
1192 infot = 1
1193 CALL ssbevd_2stage( 'V', 'U', 0, 0, a, 1, x, z, 1, w,
1194 $ 1, iw, 1, info )
1195 CALL chkxer( 'SSBEVD_2STAGE', infot, nout, lerr, ok )
1196 infot = 2
1197 CALL ssbevd_2stage( 'N', '/', 0, 0, a, 1, x, z, 1, w,
1198 $ 1, iw, 1, info )
1199 CALL chkxer( 'SSBEVD_2STAGE', infot, nout, lerr, ok )
1200 infot = 3
1201 CALL ssbevd_2stage( 'N', 'U', -1, 0, a, 1, x, z, 1, w,
1202 $ 1, iw, 1, info )
1203 CALL chkxer( 'SSBEVD_2STAGE', infot, nout, lerr, ok )
1204 infot = 4
1205 CALL ssbevd_2stage( 'N', 'U', 0, -1, a, 1, x, z, 1, w,
1206 $ 1, iw, 1, info )
1207 CALL chkxer( 'SSBEVD_2STAGE', infot, nout, lerr, ok )
1208 infot = 6
1209 CALL ssbevd_2stage( 'N', 'U', 2, 1, a, 1, x, z, 1, w,
1210 $ 4, iw, 1, info )
1211 CALL chkxer( 'SSBEVD_2STAGE', infot, nout, lerr, ok )
1212* INFOT = 9
1213* CALL SSBEVD_2STAGE( 'V', 'U', 2, 1, A, 2, X, Z, 1, W,
1214* $ 25, IW, 12, INFO )
1215* CALL CHKXER( 'SSBEVD_2STAGE', INFOT, NOUT, LERR, OK )
1216 infot = 11
1217 CALL ssbevd_2stage( 'N', 'U', 1, 0, a, 1, x, z, 1, w,
1218 $ 0, iw, 1, info )
1219 CALL chkxer( 'SSBEVD_2STAGE', infot, nout, lerr, ok )
1220 infot = 11
1221 CALL ssbevd_2stage( 'N', 'U', 2, 0, a, 1, x, z, 1, w,
1222 $ 3, iw, 1, info )
1223 CALL chkxer( 'SSBEVD_2STAGE', infot, nout, lerr, ok )
1224* INFOT = 11
1225* CALL SSBEVD_2STAGE( 'V', 'U', 2, 0, A, 1, X, Z, 2, W,
1226* $ 18, IW, 12, INFO )
1227* CALL CHKXER( 'SSBEVD_2STAGE', INFOT, NOUT, LERR, OK )
1228 infot = 13
1229 CALL ssbevd_2stage( 'N', 'U', 1, 0, a, 1, x, z, 1, w,
1230 $ 1, iw, 0, info )
1231 CALL chkxer( 'SSBEVD_2STAGE', infot, nout, lerr, ok )
1232* INFOT = 13
1233* CALL SSBEVD_2STAGE( 'V', 'U', 2, 0, A, 1, X, Z, 2, W,
1234* $ 25, IW, 11, INFO )
1235* CALL CHKXER( 'SSBEVD_2STAGE', INFOT, NOUT, LERR, OK )
1236* NT = NT + 12
1237 nt = nt + 9
1238*
1239* SSBEV
1240*
1241 srnamt = 'SSBEV '
1242 infot = 1
1243 CALL ssbev( '/', 'U', 0, 0, a, 1, x, z, 1, w, info )
1244 CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
1245 infot = 2
1246 CALL ssbev( 'N', '/', 0, 0, a, 1, x, z, 1, w, info )
1247 CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
1248 infot = 3
1249 CALL ssbev( 'N', 'U', -1, 0, a, 1, x, z, 1, w, info )
1250 CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
1251 infot = 4
1252 CALL ssbev( 'N', 'U', 0, -1, a, 1, x, z, 1, w, info )
1253 CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
1254 infot = 6
1255 CALL ssbev( 'N', 'U', 2, 1, a, 1, x, z, 1, w, info )
1256 CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
1257 infot = 9
1258 CALL ssbev( 'V', 'U', 2, 0, a, 1, x, z, 1, w, info )
1259 CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
1260 nt = nt + 6
1261*
1262* SSBEV_2STAGE
1263*
1264 srnamt = 'SSBEV_2STAGE '
1265 infot = 1
1266 CALL ssbev_2stage( '/', 'U', 0, 0, a, 1, x, z, 1, w, 0, info )
1267 CALL chkxer( 'SSBEV_2STAGE ', infot, nout, lerr, ok )
1268 infot = 1
1269 CALL ssbev_2stage( 'V', 'U', 0, 0, a, 1, x, z, 1, w, 0, info )
1270 CALL chkxer( 'SSBEV_2STAGE ', infot, nout, lerr, ok )
1271 infot = 2
1272 CALL ssbev_2stage( 'N', '/', 0, 0, a, 1, x, z, 1, w, 0, info )
1273 CALL chkxer( 'SSBEV_2STAGE ', infot, nout, lerr, ok )
1274 infot = 3
1275 CALL ssbev_2stage( 'N', 'U', -1, 0, a, 1, x, z, 1, w, 0, info )
1276 CALL chkxer( 'SSBEV_2STAGE ', infot, nout, lerr, ok )
1277 infot = 4
1278 CALL ssbev_2stage( 'N', 'U', 0, -1, a, 1, x, z, 1, w, 0, info )
1279 CALL chkxer( 'SSBEV_2STAGE ', infot, nout, lerr, ok )
1280 infot = 6
1281 CALL ssbev_2stage( 'N', 'U', 2, 1, a, 1, x, z, 1, w, 0, info )
1282 CALL chkxer( 'SSBEV_2STAGE ', infot, nout, lerr, ok )
1283 infot = 9
1284 CALL ssbev_2stage( 'N', 'U', 2, 0, a, 1, x, z, 0, w, 0, info )
1285 CALL chkxer( 'SSBEV_2STAGE ', infot, nout, lerr, ok )
1286 infot = 11
1287 CALL ssbev_2stage( 'N', 'U', 0, 0, a, 1, x, z, 1, w, 0, info )
1288 CALL chkxer( 'SSBEV_2STAGE ', infot, nout, lerr, ok )
1289 nt = nt + 8
1290*
1291* SSBEVX
1292*
1293 srnamt = 'SSBEVX'
1294 infot = 1
1295 CALL ssbevx( '/', 'A', 'U', 0, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
1296 $ 0.0, m, x, z, 1, w, iw, i3, info )
1297 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1298 infot = 2
1299 CALL ssbevx( 'N', '/', 'U', 0, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
1300 $ 0.0, m, x, z, 1, w, iw, i3, info )
1301 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1302 infot = 3
1303 CALL ssbevx( 'N', 'A', '/', 0, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
1304 $ 0.0, m, x, z, 1, w, iw, i3, info )
1305 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1306 infot = 4
1307 CALL ssbevx( 'N', 'A', 'U', -1, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
1308 $ 0.0, m, x, z, 1, w, iw, i3, info )
1309 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1310 infot = 5
1311 CALL ssbevx( 'N', 'A', 'U', 0, -1, a, 1, q, 1, 0.0, 0.0, 0, 0,
1312 $ 0.0, m, x, z, 1, w, iw, i3, info )
1313 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1314 infot = 7
1315 CALL ssbevx( 'N', 'A', 'U', 2, 1, a, 1, q, 1, 0.0, 0.0, 0, 0,
1316 $ 0.0, m, x, z, 1, w, iw, i3, info )
1317 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1318 infot = 9
1319 CALL ssbevx( 'V', 'A', 'U', 2, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
1320 $ 0.0, m, x, z, 2, w, iw, i3, info )
1321 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1322 infot = 11
1323 CALL ssbevx( 'N', 'V', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
1324 $ 0.0, m, x, z, 1, w, iw, i3, info )
1325 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1326 infot = 12
1327 CALL ssbevx( 'N', 'I', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
1328 $ 0.0, m, x, z, 1, w, iw, i3, info )
1329 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1330 infot = 12
1331 CALL ssbevx( 'N', 'I', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 2, 1,
1332 $ 0.0, m, x, z, 1, w, iw, i3, info )
1333 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1334 infot = 13
1335 CALL ssbevx( 'N', 'I', 'U', 2, 0, a, 1, q, 1, 0.0, 0.0, 2, 1,
1336 $ 0.0, m, x, z, 1, w, iw, i3, info )
1337 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1338 infot = 13
1339 CALL ssbevx( 'N', 'I', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 1, 2,
1340 $ 0.0, m, x, z, 1, w, iw, i3, info )
1341 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1342 infot = 18
1343 CALL ssbevx( 'V', 'A', 'U', 2, 0, a, 1, q, 2, 0.0, 0.0, 0, 0,
1344 $ 0.0, m, x, z, 1, w, iw, i3, info )
1345 CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
1346 nt = nt + 13
1347*
1348* SSBEVX_2STAGE
1349*
1350 srnamt = 'SSBEVX_2STAGE'
1351 infot = 1
1352 CALL ssbevx_2stage( '/', 'A', 'U', 0, 0, a, 1, q, 1, 0.0e0,
1353 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1354 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1355 infot = 1
1356 CALL ssbevx_2stage( 'V', 'A', 'U', 0, 0, a, 1, q, 1, 0.0e0,
1357 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1358 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1359 infot = 2
1360 CALL ssbevx_2stage( 'N', '/', 'U', 0, 0, a, 1, q, 1, 0.0e0,
1361 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1362 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1363 infot = 3
1364 CALL ssbevx_2stage( 'N', 'A', '/', 0, 0, a, 1, q, 1, 0.0e0,
1365 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1366 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1367 infot = 4
1368 CALL ssbevx_2stage( 'N', 'A', 'U', -1, 0, a, 1, q, 1, 0.0e0,
1369 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1370 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1371 infot = 5
1372 CALL ssbevx_2stage( 'N', 'A', 'U', 0, -1, a, 1, q, 1, 0.0e0,
1373 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1374 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1375 infot = 7
1376 CALL ssbevx_2stage( 'N', 'A', 'U', 2, 1, a, 1, q, 1, 0.0e0,
1377 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1378 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1379* INFOT = 9
1380* CALL SSBEVX_2STAGE( 'V', 'A', 'U', 2, 0, A, 1, Q, 1, 0.0E0,
1381* $ 0.0E0, 0, 0, 0.0E0, M, X, Z, 2, W, 0, IW, I3, INFO )
1382* CALL CHKXER( 'SSBEVX_2STAGE', INFOT, NOUT, LERR, OK )
1383 infot = 11
1384 CALL ssbevx_2stage( 'N', 'V', 'U', 1, 0, a, 1, q, 1, 0.0e0,
1385 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1386 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1387 infot = 12
1388 CALL ssbevx_2stage( 'N', 'I', 'U', 1, 0, a, 1, q, 1, 0.0e0,
1389 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1390 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1391 infot = 12
1392 CALL ssbevx_2stage( 'N', 'I', 'U', 1, 0, a, 1, q, 1, 0.0e0,
1393 $ 0.0e0, 2, 1, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1394 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1395 infot = 13
1396 CALL ssbevx_2stage( 'N', 'I', 'U', 2, 0, a, 1, q, 1, 0.0e0,
1397 $ 0.0e0, 2, 1, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1398 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1399 infot = 13
1400 CALL ssbevx_2stage( 'N', 'I', 'U', 1, 0, a, 1, q, 1, 0.0e0,
1401 $ 0.0e0, 1, 2, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1402 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1403* INFOT = 18
1404* CALL SSBEVX_2STAGE( 'V', 'A', 'U', 2, 0, A, 1, Q, 2, 0.0E0,
1405* $ 0.0E0, 0, 0, 0.0E0, M, X, Z, 1, W, 0, IW, I3, INFO )
1406* CALL CHKXER( 'SSBEVX_2STAGE', INFOT, NOUT, LERR, OK )
1407 infot = 20
1408 CALL ssbevx_2stage( 'N', 'A', 'U', 0, 0, a, 1, q, 1, 0.0e0,
1409 $ 0.0e0, 0, 0, 0.0e0, m, x, z, 1, w, 0, iw, i3, info )
1410 CALL chkxer( 'SSBEVX_2STAGE', infot, nout, lerr, ok )
1411* NT = NT + 15
1412 nt = nt + 13
1413 END IF
1414*
1415* Print a summary line.
1416*
1417 IF( ok ) THEN
1418 WRITE( nout, fmt = 9999 )path, nt
1419 ELSE
1420 WRITE( nout, fmt = 9998 )path
1421 END IF
1422*
1423 9999 FORMAT( 1x, a3, ' routines passed the tests of the error exits',
1424 $ ' (', i3, ' tests done)' )
1425 9998 FORMAT( ' *** ', a3, ' routines failed the tests of the error ',
1426 $ 'exits ***' )
1427*
1428 RETURN
1429*
1430* End of SERRST
1431*
1432 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine ssbev_2stage(jobz, uplo, n, kd, ab, ldab, w, z, ldz, work, lwork, info)
SSBEV_2STAGE computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER m...
subroutine ssbev(jobz, uplo, n, kd, ab, ldab, w, z, ldz, work, info)
SSBEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrices
Definition ssbev.f:146
subroutine ssbevd_2stage(jobz, uplo, n, kd, ab, ldab, w, z, ldz, work, lwork, iwork, liwork, info)
SSBEVD_2STAGE computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER ...
subroutine ssbevd(jobz, uplo, n, kd, ab, ldab, w, z, ldz, work, lwork, iwork, liwork, info)
SSBEVD computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrice...
Definition ssbevd.f:187
subroutine ssbevx_2stage(jobz, range, uplo, n, kd, ab, ldab, q, ldq, vl, vu, il, iu, abstol, m, w, z, ldz, work, lwork, iwork, ifail, info)
SSBEVX_2STAGE computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER ...
subroutine ssbevx(jobz, range, uplo, n, kd, ab, ldab, q, ldq, vl, vu, il, iu, abstol, m, w, z, ldz, work, iwork, ifail, info)
SSBEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrice...
Definition ssbevx.f:265
subroutine ssbtrd(vect, uplo, n, kd, ab, ldab, d, e, q, ldq, work, info)
SSBTRD
Definition ssbtrd.f:163
subroutine ssyev_2stage(jobz, uplo, n, a, lda, w, work, lwork, info)
SSYEV_2STAGE computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY matr...
subroutine ssyev(jobz, uplo, n, a, lda, w, work, lwork, info)
SSYEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY matrices
Definition ssyev.f:132
subroutine ssyevd_2stage(jobz, uplo, n, a, lda, w, work, lwork, iwork, liwork, info)
SSYEVD_2STAGE computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY mat...
subroutine ssyevd(jobz, uplo, n, a, lda, w, work, lwork, iwork, liwork, info)
SSYEVD computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY matrices
Definition ssyevd.f:176
subroutine ssyevr_2stage(jobz, range, uplo, n, a, lda, vl, vu, il, iu, abstol, m, w, z, ldz, isuppz, work, lwork, iwork, liwork, info)
SSYEVR_2STAGE computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY mat...
subroutine ssyevr(jobz, range, uplo, n, a, lda, vl, vu, il, iu, abstol, m, w, z, ldz, isuppz, work, lwork, iwork, liwork, info)
SSYEVR computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY matrices
Definition ssyevr.f:336
subroutine ssyevx_2stage(jobz, range, uplo, n, a, lda, vl, vu, il, iu, abstol, m, w, z, ldz, work, lwork, iwork, ifail, info)
SSYEVX_2STAGE computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY mat...
subroutine ssyevx(jobz, range, uplo, n, a, lda, vl, vu, il, iu, abstol, m, w, z, ldz, work, lwork, iwork, ifail, info)
SSYEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY matrices
Definition ssyevx.f:253
subroutine ssytd2(uplo, n, a, lda, d, e, tau, info)
SSYTD2 reduces a symmetric matrix to real symmetric tridiagonal form by an orthogonal similarity tran...
Definition ssytd2.f:173
subroutine ssytrd_2stage(vect, uplo, n, a, lda, d, e, tau, hous2, lhous2, work, lwork, info)
SSYTRD_2STAGE
subroutine ssytrd_sb2st(stage1, vect, uplo, n, kd, ab, ldab, d, e, hous, lhous, work, lwork, info)
SSYTRD_SB2ST reduces a real symmetric band matrix A to real symmetric tridiagonal form T
subroutine ssytrd_sy2sb(uplo, n, kd, a, lda, ab, ldab, tau, work, lwork, info)
SSYTRD_SY2SB
subroutine ssytrd(uplo, n, a, lda, d, e, tau, work, lwork, info)
SSYTRD
Definition ssytrd.f:192
subroutine sspev(jobz, uplo, n, ap, w, z, ldz, work, info)
SSPEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrices
Definition sspev.f:130
subroutine sspevd(jobz, uplo, n, ap, w, z, ldz, work, lwork, iwork, liwork, info)
SSPEVD computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrice...
Definition sspevd.f:172
subroutine sspevx(jobz, range, uplo, n, ap, vl, vu, il, iu, abstol, m, w, z, ldz, work, iwork, ifail, info)
SSPEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrice...
Definition sspevx.f:234
subroutine ssptrd(uplo, n, ap, d, e, tau, info)
SSPTRD
Definition ssptrd.f:150
subroutine spteqr(compz, n, d, e, z, ldz, work, info)
SPTEQR
Definition spteqr.f:145
subroutine sstebz(range, order, n, vl, vu, il, iu, abstol, d, e, m, nsplit, w, iblock, isplit, work, iwork, info)
SSTEBZ
Definition sstebz.f:273
subroutine sstedc(compz, n, d, e, z, ldz, work, lwork, iwork, liwork, info)
SSTEDC
Definition sstedc.f:182
subroutine sstein(n, d, e, m, w, iblock, isplit, z, ldz, work, iwork, ifail, info)
SSTEIN
Definition sstein.f:174
subroutine ssteqr(compz, n, d, e, z, ldz, work, info)
SSTEQR
Definition ssteqr.f:131
subroutine ssterf(n, d, e, info)
SSTERF
Definition ssterf.f:86
subroutine sstev(jobz, n, d, e, z, ldz, work, info)
SSTEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrices
Definition sstev.f:116
subroutine sstevd(jobz, n, d, e, z, ldz, work, lwork, iwork, liwork, info)
SSTEVD computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrice...
Definition sstevd.f:157
subroutine sstevr(jobz, range, n, d, e, vl, vu, il, iu, abstol, m, w, z, ldz, isuppz, work, lwork, iwork, liwork, info)
SSTEVR computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrice...
Definition sstevr.f:306
subroutine sstevx(jobz, range, n, d, e, vl, vu, il, iu, abstol, m, w, z, ldz, work, iwork, ifail, info)
SSTEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrice...
Definition sstevx.f:227
subroutine sorgtr(uplo, n, a, lda, tau, work, lwork, info)
SORGTR
Definition sorgtr.f:123
subroutine sormtr(side, uplo, trans, m, n, a, lda, tau, c, ldc, work, lwork, info)
SORMTR
Definition sormtr.f:172
subroutine sopgtr(uplo, n, ap, tau, q, ldq, work, info)
SOPGTR
Definition sopgtr.f:114
subroutine sopmtr(side, uplo, trans, m, n, ap, tau, c, ldc, work, info)
SOPMTR
Definition sopmtr.f:150
subroutine serrst(path, nunit)
SERRST
Definition serrst.f:61