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