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