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