LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine serrst ( character*3  PATH,
integer  NUNIT 
)

SERRST

Purpose:
 SERRST tests the error exits for SSYTRD, SORGTR, SORMTR, SSPTRD,
 SOPGTR, SOPMTR, SSTEQR, SSTERF, SSTEBZ, SSTEIN, SPTEQR, SSBTRD,
 SSYEV, SSYEVX, SSYEVD, SSBEV, SSBEVX, SSBEVD,
 SSPEV, SSPEVX, SSPEVD, SSTEV, SSTEVX, SSTEVD, and SSTEDC.
Parameters
[in]PATH
          PATH is CHARACTER*3
          The LAPACK path name for the routines to be tested.
[in]NUNIT
          NUNIT is INTEGER
          The unit number for output.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 59 of file serrst.f.

59 *
60 * -- LAPACK test routine (version 3.4.0) --
61 * -- LAPACK is a software package provided by Univ. of Tennessee, --
62 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
63 * November 2011
64 *
65 * .. Scalar Arguments ..
66  CHARACTER*3 path
67  INTEGER nunit
68 * ..
69 *
70 * =====================================================================
71 *
72 * NMAX has to be at least 3 or LIW may be too small
73 * .. Parameters ..
74  INTEGER nmax, liw, lw
75  parameter ( nmax = 3, liw = 12*nmax, lw = 20*nmax )
76 * ..
77 * .. Local Scalars ..
78  CHARACTER*2 c2
79  INTEGER i, info, j, m, n, nsplit, nt
80 * ..
81 * .. Local Arrays ..
82  INTEGER i1( nmax ), i2( nmax ), i3( nmax ), iw( liw )
83  REAL a( nmax, nmax ), c( nmax, nmax ), d( nmax ),
84  $ e( nmax ), q( nmax, nmax ), r( nmax ),
85  $ tau( nmax ), w( lw ), x( nmax ),
86  $ z( nmax, nmax )
87 * ..
88 * .. External Functions ..
89  LOGICAL lsamen
90  EXTERNAL lsamen
91 * ..
92 * .. External Subroutines ..
93  EXTERNAL chkxer, sopgtr, sopmtr, sorgtr, sormtr, spteqr,
98 * ..
99 * .. Scalars in Common ..
100  LOGICAL lerr, ok
101  CHARACTER*32 srnamt
102  INTEGER infot, nout
103 * ..
104 * .. Common blocks ..
105  COMMON / infoc / infot, nout, ok, lerr
106  COMMON / srnamc / srnamt
107 * ..
108 * .. Intrinsic Functions ..
109  INTRINSIC real
110 * ..
111 * .. Executable Statements ..
112 *
113  nout = nunit
114  WRITE( nout, fmt = * )
115  c2 = path( 2: 3 )
116 *
117 * Set the variables to innocuous values.
118 *
119  DO 20 j = 1, nmax
120  DO 10 i = 1, nmax
121  a( i, j ) = 1. / REAL( i+j )
122  10 CONTINUE
123  20 CONTINUE
124  DO 30 j = 1, nmax
125  d( j ) = REAL( j )
126  e( j ) = 0.0
127  i1( j ) = j
128  i2( j ) = j
129  tau( j ) = 1.
130  30 CONTINUE
131  ok = .true.
132  nt = 0
133 *
134 * Test error exits for the ST path.
135 *
136  IF( lsamen( 2, c2, 'ST' ) ) THEN
137 *
138 * SSYTRD
139 *
140  srnamt = 'SSYTRD'
141  infot = 1
142  CALL ssytrd( '/', 0, a, 1, d, e, tau, w, 1, info )
143  CALL chkxer( 'SSYTRD', infot, nout, lerr, ok )
144  infot = 2
145  CALL ssytrd( 'U', -1, a, 1, d, e, tau, w, 1, info )
146  CALL chkxer( 'SSYTRD', infot, nout, lerr, ok )
147  infot = 4
148  CALL ssytrd( 'U', 2, a, 1, d, e, tau, w, 1, info )
149  CALL chkxer( 'SSYTRD', infot, nout, lerr, ok )
150  infot = 9
151  CALL ssytrd( 'U', 0, a, 1, d, e, tau, w, 0, info )
152  CALL chkxer( 'SSYTRD', infot, nout, lerr, ok )
153  nt = nt + 4
154 *
155 * SORGTR
156 *
157  srnamt = 'SORGTR'
158  infot = 1
159  CALL sorgtr( '/', 0, a, 1, tau, w, 1, info )
160  CALL chkxer( 'SORGTR', infot, nout, lerr, ok )
161  infot = 2
162  CALL sorgtr( 'U', -1, a, 1, tau, w, 1, info )
163  CALL chkxer( 'SORGTR', infot, nout, lerr, ok )
164  infot = 4
165  CALL sorgtr( 'U', 2, a, 1, tau, w, 1, info )
166  CALL chkxer( 'SORGTR', infot, nout, lerr, ok )
167  infot = 7
168  CALL sorgtr( 'U', 3, a, 3, tau, w, 1, info )
169  CALL chkxer( 'SORGTR', infot, nout, lerr, ok )
170  nt = nt + 4
171 *
172 * SORMTR
173 *
174  srnamt = 'SORMTR'
175  infot = 1
176  CALL sormtr( '/', 'U', 'N', 0, 0, a, 1, tau, c, 1, w, 1, info )
177  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
178  infot = 2
179  CALL sormtr( 'L', '/', 'N', 0, 0, a, 1, tau, c, 1, w, 1, info )
180  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
181  infot = 3
182  CALL sormtr( 'L', 'U', '/', 0, 0, a, 1, tau, c, 1, w, 1, info )
183  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
184  infot = 4
185  CALL sormtr( 'L', 'U', 'N', -1, 0, a, 1, tau, c, 1, w, 1,
186  $ info )
187  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
188  infot = 5
189  CALL sormtr( 'L', 'U', 'N', 0, -1, a, 1, tau, c, 1, w, 1,
190  $ info )
191  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
192  infot = 7
193  CALL sormtr( 'L', 'U', 'N', 2, 0, a, 1, tau, c, 2, w, 1, info )
194  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
195  infot = 7
196  CALL sormtr( 'R', 'U', 'N', 0, 2, a, 1, tau, c, 1, w, 1, info )
197  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
198  infot = 10
199  CALL sormtr( 'L', 'U', 'N', 2, 0, a, 2, tau, c, 1, w, 1, info )
200  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
201  infot = 12
202  CALL sormtr( 'L', 'U', 'N', 0, 2, a, 1, tau, c, 1, w, 1, info )
203  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
204  infot = 12
205  CALL sormtr( 'R', 'U', 'N', 2, 0, a, 1, tau, c, 2, w, 1, info )
206  CALL chkxer( 'SORMTR', infot, nout, lerr, ok )
207  nt = nt + 10
208 *
209 * SSPTRD
210 *
211  srnamt = 'SSPTRD'
212  infot = 1
213  CALL ssptrd( '/', 0, a, d, e, tau, info )
214  CALL chkxer( 'SSPTRD', infot, nout, lerr, ok )
215  infot = 2
216  CALL ssptrd( 'U', -1, a, d, e, tau, info )
217  CALL chkxer( 'SSPTRD', infot, nout, lerr, ok )
218  nt = nt + 2
219 *
220 * SOPGTR
221 *
222  srnamt = 'SOPGTR'
223  infot = 1
224  CALL sopgtr( '/', 0, a, tau, z, 1, w, info )
225  CALL chkxer( 'SOPGTR', infot, nout, lerr, ok )
226  infot = 2
227  CALL sopgtr( 'U', -1, a, tau, z, 1, w, info )
228  CALL chkxer( 'SOPGTR', infot, nout, lerr, ok )
229  infot = 6
230  CALL sopgtr( 'U', 2, a, tau, z, 1, w, info )
231  CALL chkxer( 'SOPGTR', infot, nout, lerr, ok )
232  nt = nt + 3
233 *
234 * SOPMTR
235 *
236  srnamt = 'SOPMTR'
237  infot = 1
238  CALL sopmtr( '/', 'U', 'N', 0, 0, a, tau, c, 1, w, info )
239  CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
240  infot = 2
241  CALL sopmtr( 'L', '/', 'N', 0, 0, a, tau, c, 1, w, info )
242  CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
243  infot = 3
244  CALL sopmtr( 'L', 'U', '/', 0, 0, a, tau, c, 1, w, info )
245  CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
246  infot = 4
247  CALL sopmtr( 'L', 'U', 'N', -1, 0, a, tau, c, 1, w, info )
248  CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
249  infot = 5
250  CALL sopmtr( 'L', 'U', 'N', 0, -1, a, tau, c, 1, w, info )
251  CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
252  infot = 9
253  CALL sopmtr( 'L', 'U', 'N', 2, 0, a, tau, c, 1, w, info )
254  CALL chkxer( 'SOPMTR', infot, nout, lerr, ok )
255  nt = nt + 6
256 *
257 * SPTEQR
258 *
259  srnamt = 'SPTEQR'
260  infot = 1
261  CALL spteqr( '/', 0, d, e, z, 1, w, info )
262  CALL chkxer( 'SPTEQR', infot, nout, lerr, ok )
263  infot = 2
264  CALL spteqr( 'N', -1, d, e, z, 1, w, info )
265  CALL chkxer( 'SPTEQR', infot, nout, lerr, ok )
266  infot = 6
267  CALL spteqr( 'V', 2, d, e, z, 1, w, info )
268  CALL chkxer( 'SPTEQR', infot, nout, lerr, ok )
269  nt = nt + 3
270 *
271 * SSTEBZ
272 *
273  srnamt = 'SSTEBZ'
274  infot = 1
275  CALL sstebz( '/', 'E', 0, 0.0, 1.0, 1, 0, 0.0, d, e, m, nsplit,
276  $ x, i1, i2, w, iw, info )
277  CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
278  infot = 2
279  CALL sstebz( 'A', '/', 0, 0.0, 0.0, 0, 0, 0.0, d, e, m, nsplit,
280  $ x, i1, i2, w, iw, info )
281  CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
282  infot = 3
283  CALL sstebz( 'A', 'E', -1, 0.0, 0.0, 0, 0, 0.0, d, e, m,
284  $ nsplit, x, i1, i2, w, iw, info )
285  CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
286  infot = 5
287  CALL sstebz( 'V', 'E', 0, 0.0, 0.0, 0, 0, 0.0, d, e, m, nsplit,
288  $ x, i1, i2, w, iw, info )
289  CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
290  infot = 6
291  CALL sstebz( 'I', 'E', 0, 0.0, 0.0, 0, 0, 0.0, d, e, m, nsplit,
292  $ x, i1, i2, w, iw, info )
293  CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
294  infot = 6
295  CALL sstebz( 'I', 'E', 1, 0.0, 0.0, 2, 1, 0.0, d, e, m, nsplit,
296  $ x, i1, i2, w, iw, info )
297  CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
298  infot = 7
299  CALL sstebz( 'I', 'E', 1, 0.0, 0.0, 1, 0, 0.0, d, e, m, nsplit,
300  $ x, i1, i2, w, iw, info )
301  CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
302  infot = 7
303  CALL sstebz( 'I', 'E', 1, 0.0, 0.0, 1, 2, 0.0, d, e, m, nsplit,
304  $ x, i1, i2, w, iw, info )
305  CALL chkxer( 'SSTEBZ', infot, nout, lerr, ok )
306  nt = nt + 8
307 *
308 * SSTEIN
309 *
310  srnamt = 'SSTEIN'
311  infot = 1
312  CALL sstein( -1, d, e, 0, x, i1, i2, z, 1, w, iw, i3, info )
313  CALL chkxer( 'SSTEIN', infot, nout, lerr, ok )
314  infot = 4
315  CALL sstein( 0, d, e, -1, x, i1, i2, z, 1, w, iw, i3, info )
316  CALL chkxer( 'SSTEIN', infot, nout, lerr, ok )
317  infot = 4
318  CALL sstein( 0, d, e, 1, x, i1, i2, z, 1, w, iw, i3, info )
319  CALL chkxer( 'SSTEIN', infot, nout, lerr, ok )
320  infot = 9
321  CALL sstein( 2, d, e, 0, x, i1, i2, z, 1, w, iw, i3, info )
322  CALL chkxer( 'SSTEIN', infot, nout, lerr, ok )
323  nt = nt + 4
324 *
325 * SSTEQR
326 *
327  srnamt = 'SSTEQR'
328  infot = 1
329  CALL ssteqr( '/', 0, d, e, z, 1, w, info )
330  CALL chkxer( 'SSTEQR', infot, nout, lerr, ok )
331  infot = 2
332  CALL ssteqr( 'N', -1, d, e, z, 1, w, info )
333  CALL chkxer( 'SSTEQR', infot, nout, lerr, ok )
334  infot = 6
335  CALL ssteqr( 'V', 2, d, e, z, 1, w, info )
336  CALL chkxer( 'SSTEQR', infot, nout, lerr, ok )
337  nt = nt + 3
338 *
339 * SSTERF
340 *
341  srnamt = 'SSTERF'
342  infot = 1
343  CALL ssterf( -1, d, e, info )
344  CALL chkxer( 'SSTERF', infot, nout, lerr, ok )
345  nt = nt + 1
346 *
347 * SSTEDC
348 *
349  srnamt = 'SSTEDC'
350  infot = 1
351  CALL sstedc( '/', 0, d, e, z, 1, w, 1, iw, 1, info )
352  CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
353  infot = 2
354  CALL sstedc( 'N', -1, d, e, z, 1, w, 1, iw, 1, info )
355  CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
356  infot = 6
357  CALL sstedc( 'V', 2, d, e, z, 1, w, 23, iw, 28, info )
358  CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
359  infot = 8
360  CALL sstedc( 'N', 1, d, e, z, 1, w, 0, iw, 1, info )
361  CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
362  infot = 8
363  CALL sstedc( 'I', 2, d, e, z, 2, w, 0, iw, 12, info )
364  CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
365  infot = 8
366  CALL sstedc( 'V', 2, d, e, z, 2, w, 0, iw, 28, info )
367  CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
368  infot = 10
369  CALL sstedc( 'N', 1, d, e, z, 1, w, 1, iw, 0, info )
370  CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
371  infot = 10
372  CALL sstedc( 'I', 2, d, e, z, 2, w, 19, iw, 0, info )
373  CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
374  infot = 10
375  CALL sstedc( 'V', 2, d, e, z, 2, w, 23, iw, 0, info )
376  CALL chkxer( 'SSTEDC', infot, nout, lerr, ok )
377  nt = nt + 9
378 *
379 * SSTEVD
380 *
381  srnamt = 'SSTEVD'
382  infot = 1
383  CALL sstevd( '/', 0, d, e, z, 1, w, 1, iw, 1, info )
384  CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
385  infot = 2
386  CALL sstevd( 'N', -1, d, e, z, 1, w, 1, iw, 1, info )
387  CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
388  infot = 6
389  CALL sstevd( 'V', 2, d, e, z, 1, w, 19, iw, 12, info )
390  CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
391  infot = 8
392  CALL sstevd( 'N', 1, d, e, z, 1, w, 0, iw, 1, info )
393  CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
394  infot = 8
395  CALL sstevd( 'V', 2, d, e, z, 2, w, 12, iw, 12, info )
396  CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
397  infot = 10
398  CALL sstevd( 'N', 0, d, e, z, 1, w, 1, iw, 0, info )
399  CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
400  infot = 10
401  CALL sstevd( 'V', 2, d, e, z, 2, w, 19, iw, 11, info )
402  CALL chkxer( 'SSTEVD', infot, nout, lerr, ok )
403  nt = nt + 7
404 *
405 * SSTEV
406 *
407  srnamt = 'SSTEV '
408  infot = 1
409  CALL sstev( '/', 0, d, e, z, 1, w, info )
410  CALL chkxer( 'SSTEV ', infot, nout, lerr, ok )
411  infot = 2
412  CALL sstev( 'N', -1, d, e, z, 1, w, info )
413  CALL chkxer( 'SSTEV ', infot, nout, lerr, ok )
414  infot = 6
415  CALL sstev( 'V', 2, d, e, z, 1, w, info )
416  CALL chkxer( 'SSTEV ', infot, nout, lerr, ok )
417  nt = nt + 3
418 *
419 * SSTEVX
420 *
421  srnamt = 'SSTEVX'
422  infot = 1
423  CALL sstevx( '/', 'A', 0, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
424  $ 1, w, iw, i3, info )
425  CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
426  infot = 2
427  CALL sstevx( 'N', '/', 0, d, e, 0.0, 1.0, 1, 0, 0.0, m, x, z,
428  $ 1, w, iw, i3, info )
429  CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
430  infot = 3
431  CALL sstevx( 'N', 'A', -1, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
432  $ 1, w, iw, i3, info )
433  CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
434  infot = 7
435  CALL sstevx( 'N', 'V', 1, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
436  $ 1, w, iw, i3, info )
437  CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
438  infot = 8
439  CALL sstevx( 'N', 'I', 1, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
440  $ 1, w, iw, i3, info )
441  CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
442  infot = 8
443  CALL sstevx( 'N', 'I', 1, d, e, 0.0, 0.0, 2, 1, 0.0, m, x, z,
444  $ 1, w, iw, i3, info )
445  CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
446  infot = 9
447  CALL sstevx( 'N', 'I', 2, d, e, 0.0, 0.0, 2, 1, 0.0, m, x, z,
448  $ 1, w, iw, i3, info )
449  CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
450  infot = 9
451  CALL sstevx( 'N', 'I', 1, d, e, 0.0, 0.0, 1, 2, 0.0, m, x, z,
452  $ 1, w, iw, i3, info )
453  CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
454  infot = 14
455  CALL sstevx( 'V', 'A', 2, d, e, 0.0, 0.0, 0, 0, 0.0, m, x, z,
456  $ 1, w, iw, i3, info )
457  CALL chkxer( 'SSTEVX', infot, nout, lerr, ok )
458  nt = nt + 9
459 *
460 * SSTEVR
461 *
462  n = 1
463  srnamt = 'SSTEVR'
464  infot = 1
465  CALL sstevr( '/', 'A', 0, d, e, 0.0, 0.0, 1, 1, 0.0, m, r, z,
466  $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
467  CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
468  infot = 2
469  CALL sstevr( 'V', '/', 0, d, e, 0.0, 0.0, 1, 1, 0.0, m, r, z,
470  $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
471  CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
472  infot = 3
473  CALL sstevr( 'V', 'A', -1, d, e, 0.0, 0.0, 1, 1, 0.0, m, r, z,
474  $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
475  CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
476  infot = 7
477  CALL sstevr( 'V', 'V', 1, d, e, 0.0, 0.0, 1, 1, 0.0, m, r, z,
478  $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
479  CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
480  infot = 8
481  CALL sstevr( 'V', 'I', 1, d, e, 0.0, 0.0, 0, 1, 0.0, m, w, z,
482  $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
483  CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
484  infot = 9
485  n = 2
486  CALL sstevr( 'V', 'I', 2, d, e, 0.0, 0.0, 2, 1, 0.0, m, w, z,
487  $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
488  CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
489  infot = 14
490  n = 1
491  CALL sstevr( 'V', 'I', 1, d, e, 0.0, 0.0, 1, 1, 0.0, m, w, z,
492  $ 0, iw, x, 20*n, iw( 2*n+1 ), 10*n, info )
493  CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
494  infot = 17
495  CALL sstevr( 'V', 'I', 1, d, e, 0.0, 0.0, 1, 1, 0.0, m, w, z,
496  $ 1, iw, x, 20*n-1, iw( 2*n+1 ), 10*n, info )
497  CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
498  infot = 19
499  CALL sstevr( 'V', 'I', 1, d, e, 0.0, 0.0, 1, 1, 0.0, m, w, z,
500  $ 1, iw, x, 20*n, iw( 2*n+1 ), 10*n-1, info )
501  CALL chkxer( 'SSTEVR', infot, nout, lerr, ok )
502  nt = nt + 9
503 *
504 * SSYEVD
505 *
506  srnamt = 'SSYEVD'
507  infot = 1
508  CALL ssyevd( '/', 'U', 0, a, 1, x, w, 1, iw, 1, info )
509  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
510  infot = 2
511  CALL ssyevd( 'N', '/', 0, a, 1, x, w, 1, iw, 1, info )
512  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
513  infot = 3
514  CALL ssyevd( 'N', 'U', -1, a, 1, x, w, 1, iw, 1, info )
515  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
516  infot = 5
517  CALL ssyevd( 'N', 'U', 2, a, 1, x, w, 3, iw, 1, info )
518  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
519  infot = 8
520  CALL ssyevd( 'N', 'U', 1, a, 1, x, w, 0, iw, 1, info )
521  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
522  infot = 8
523  CALL ssyevd( 'N', 'U', 2, a, 2, x, w, 4, iw, 1, info )
524  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
525  infot = 8
526  CALL ssyevd( 'V', 'U', 2, a, 2, x, w, 20, iw, 12, info )
527  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
528  infot = 10
529  CALL ssyevd( 'N', 'U', 1, a, 1, x, w, 1, iw, 0, info )
530  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
531  infot = 10
532  CALL ssyevd( 'N', 'U', 2, a, 2, x, w, 5, iw, 0, info )
533  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
534  infot = 10
535  CALL ssyevd( 'V', 'U', 2, a, 2, x, w, 27, iw, 11, info )
536  CALL chkxer( 'SSYEVD', infot, nout, lerr, ok )
537  nt = nt + 10
538 *
539 * SSYEVR
540 *
541  srnamt = 'SSYEVR'
542  n = 1
543  infot = 1
544  CALL ssyevr( '/', 'A', 'U', 0, a, 1, 0.0, 0.0, 1, 1, 0.0, m, r,
545  $ z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
546  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
547  infot = 2
548  CALL ssyevr( 'V', '/', 'U', 0, a, 1, 0.0, 0.0, 1, 1, 0.0, m, r,
549  $ z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
550  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
551  infot = 3
552  CALL ssyevr( 'V', 'A', '/', -1, a, 1, 0.0, 0.0, 1, 1, 0.0, m,
553  $ r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
554  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
555  infot = 4
556  CALL ssyevr( 'V', 'A', 'U', -1, a, 1, 0.0, 0.0, 1, 1, 0.0, m,
557  $ r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
558  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
559  infot = 6
560  CALL ssyevr( 'V', 'A', 'U', 2, a, 1, 0.0, 0.0, 1, 1, 0.0, m, r,
561  $ z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
562  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
563  infot = 8
564  CALL ssyevr( 'V', 'V', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
565  $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
566  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
567  infot = 9
568  CALL ssyevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 0, 1, 0.0,
569  $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
570  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
571  infot = 10
572 *
573  CALL ssyevr( 'V', 'I', 'U', 2, a, 2, 0.0e0, 0.0e0, 2, 1, 0.0,
574  $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
575  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
576  infot = 15
577  CALL ssyevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
578  $ m, r, z, 0, iw, q, 26*n, iw( 2*n+1 ), 10*n, info )
579  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
580  infot = 18
581  CALL ssyevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
582  $ m, r, z, 1, iw, q, 26*n-1, iw( 2*n+1 ), 10*n,
583  $ info )
584  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
585  infot = 20
586  CALL ssyevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
587  $ m, r, z, 1, iw, q, 26*n, iw( 2*n+1 ), 10*n-1,
588  $ info )
589  CALL chkxer( 'SSYEVR', infot, nout, lerr, ok )
590  nt = nt + 11
591 *
592 * SSYEV
593 *
594  srnamt = 'SSYEV '
595  infot = 1
596  CALL ssyev( '/', 'U', 0, a, 1, x, w, 1, info )
597  CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
598  infot = 2
599  CALL ssyev( 'N', '/', 0, a, 1, x, w, 1, info )
600  CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
601  infot = 3
602  CALL ssyev( 'N', 'U', -1, a, 1, x, w, 1, info )
603  CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
604  infot = 5
605  CALL ssyev( 'N', 'U', 2, a, 1, x, w, 3, info )
606  CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
607  infot = 8
608  CALL ssyev( 'N', 'U', 1, a, 1, x, w, 1, info )
609  CALL chkxer( 'SSYEV ', infot, nout, lerr, ok )
610  nt = nt + 5
611 *
612 * SSYEVX
613 *
614  srnamt = 'SSYEVX'
615  infot = 1
616  CALL ssyevx( '/', 'A', 'U', 0, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
617  $ z, 1, w, 1, iw, i3, info )
618  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
619  infot = 2
620  CALL ssyevx( 'N', '/', 'U', 0, a, 1, 0.0, 1.0, 1, 0, 0.0, m, x,
621  $ z, 1, w, 1, iw, i3, info )
622  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
623  infot = 3
624  CALL ssyevx( 'N', 'A', '/', 0, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
625  $ z, 1, w, 1, iw, i3, info )
626  infot = 4
627  CALL ssyevx( 'N', 'A', 'U', -1, a, 1, 0.0, 0.0, 0, 0, 0.0, m,
628  $ x, z, 1, w, 1, iw, i3, info )
629  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
630  infot = 6
631  CALL ssyevx( 'N', 'A', 'U', 2, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
632  $ z, 1, w, 16, iw, i3, info )
633  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
634  infot = 8
635  CALL ssyevx( 'N', 'V', 'U', 1, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
636  $ z, 1, w, 8, iw, i3, info )
637  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
638  infot = 9
639  CALL ssyevx( 'N', 'I', 'U', 1, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
640  $ z, 1, w, 8, iw, i3, info )
641  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
642  infot = 9
643  CALL ssyevx( 'N', 'I', 'U', 1, a, 1, 0.0, 0.0, 2, 1, 0.0, m, x,
644  $ z, 1, w, 8, iw, i3, info )
645  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
646  infot = 10
647  CALL ssyevx( 'N', 'I', 'U', 2, a, 2, 0.0, 0.0, 2, 1, 0.0, m, x,
648  $ z, 1, w, 16, iw, i3, info )
649  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
650  infot = 10
651  CALL ssyevx( 'N', 'I', 'U', 1, a, 1, 0.0, 0.0, 1, 2, 0.0, m, x,
652  $ z, 1, w, 8, iw, i3, info )
653  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
654  infot = 15
655  CALL ssyevx( 'V', 'A', 'U', 2, a, 2, 0.0, 0.0, 0, 0, 0.0, m, x,
656  $ z, 1, w, 16, iw, i3, info )
657  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
658  infot = 17
659  CALL ssyevx( 'V', 'A', 'U', 1, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
660  $ z, 1, w, 0, iw, i3, info )
661  CALL chkxer( 'SSYEVX', infot, nout, lerr, ok )
662  nt = nt + 12
663 *
664 * SSPEVD
665 *
666  srnamt = 'SSPEVD'
667  infot = 1
668  CALL sspevd( '/', 'U', 0, a, x, z, 1, w, 1, iw, 1, info )
669  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
670  infot = 2
671  CALL sspevd( 'N', '/', 0, a, x, z, 1, w, 1, iw, 1, info )
672  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
673  infot = 3
674  CALL sspevd( 'N', 'U', -1, a, x, z, 1, w, 1, iw, 1, info )
675  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
676  infot = 7
677  CALL sspevd( 'V', 'U', 2, a, x, z, 1, w, 23, iw, 12, info )
678  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
679  infot = 9
680  CALL sspevd( 'N', 'U', 1, a, x, z, 1, w, 0, iw, 1, info )
681  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
682  infot = 9
683  CALL sspevd( 'N', 'U', 2, a, x, z, 1, w, 3, iw, 1, info )
684  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
685  infot = 9
686  CALL sspevd( 'V', 'U', 2, a, x, z, 2, w, 16, iw, 12, info )
687  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
688  infot = 11
689  CALL sspevd( 'N', 'U', 1, a, x, z, 1, w, 1, iw, 0, info )
690  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
691  infot = 11
692  CALL sspevd( 'N', 'U', 2, a, x, z, 1, w, 4, iw, 0, info )
693  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
694  infot = 11
695  CALL sspevd( 'V', 'U', 2, a, x, z, 2, w, 23, iw, 11, info )
696  CALL chkxer( 'SSPEVD', infot, nout, lerr, ok )
697  nt = nt + 10
698 *
699 * SSPEV
700 *
701  srnamt = 'SSPEV '
702  infot = 1
703  CALL sspev( '/', 'U', 0, a, w, z, 1, x, info )
704  CALL chkxer( 'SSPEV ', infot, nout, lerr, ok )
705  infot = 2
706  CALL sspev( 'N', '/', 0, a, w, z, 1, x, info )
707  CALL chkxer( 'SSPEV ', infot, nout, lerr, ok )
708  infot = 3
709  CALL sspev( 'N', 'U', -1, a, w, z, 1, x, info )
710  CALL chkxer( 'SSPEV ', infot, nout, lerr, ok )
711  infot = 7
712  CALL sspev( 'V', 'U', 2, a, w, z, 1, x, info )
713  CALL chkxer( 'SSPEV ', infot, nout, lerr, ok )
714  nt = nt + 4
715 *
716 * SSPEVX
717 *
718  srnamt = 'SSPEVX'
719  infot = 1
720  CALL sspevx( '/', 'A', 'U', 0, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
721  $ 1, w, iw, i3, info )
722  CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
723  infot = 2
724  CALL sspevx( 'N', '/', 'U', 0, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
725  $ 1, w, iw, i3, info )
726  CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
727  infot = 3
728  CALL sspevx( 'N', 'A', '/', 0, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
729  $ 1, w, iw, i3, info )
730  infot = 4
731  CALL sspevx( 'N', 'A', 'U', -1, a, 0.0, 0.0, 0, 0, 0.0, m, x,
732  $ z, 1, w, iw, i3, info )
733  CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
734  infot = 7
735  CALL sspevx( 'N', 'V', 'U', 1, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
736  $ 1, w, iw, i3, info )
737  CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
738  infot = 8
739  CALL sspevx( 'N', 'I', 'U', 1, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
740  $ 1, w, iw, i3, info )
741  CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
742  infot = 8
743  CALL sspevx( 'N', 'I', 'U', 1, a, 0.0, 0.0, 2, 1, 0.0, m, x, z,
744  $ 1, w, iw, i3, info )
745  CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
746  infot = 9
747  CALL sspevx( 'N', 'I', 'U', 2, a, 0.0, 0.0, 2, 1, 0.0, m, x, z,
748  $ 1, w, iw, i3, info )
749  CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
750  infot = 9
751  CALL sspevx( 'N', 'I', 'U', 1, a, 0.0, 0.0, 1, 2, 0.0, m, x, z,
752  $ 1, w, iw, i3, info )
753  CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
754  infot = 14
755  CALL sspevx( 'V', 'A', 'U', 2, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
756  $ 1, w, iw, i3, info )
757  CALL chkxer( 'SSPEVX', infot, nout, lerr, ok )
758  nt = nt + 10
759 *
760 * Test error exits for the SB path.
761 *
762  ELSE IF( lsamen( 2, c2, 'SB' ) ) THEN
763 *
764 * SSBTRD
765 *
766  srnamt = 'SSBTRD'
767  infot = 1
768  CALL ssbtrd( '/', 'U', 0, 0, a, 1, d, e, z, 1, w, info )
769  CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
770  infot = 2
771  CALL ssbtrd( 'N', '/', 0, 0, a, 1, d, e, z, 1, w, info )
772  CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
773  infot = 3
774  CALL ssbtrd( 'N', 'U', -1, 0, a, 1, d, e, z, 1, w, info )
775  CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
776  infot = 4
777  CALL ssbtrd( 'N', 'U', 0, -1, a, 1, d, e, z, 1, w, info )
778  CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
779  infot = 6
780  CALL ssbtrd( 'N', 'U', 1, 1, a, 1, d, e, z, 1, w, info )
781  CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
782  infot = 10
783  CALL ssbtrd( 'V', 'U', 2, 0, a, 1, d, e, z, 1, w, info )
784  CALL chkxer( 'SSBTRD', infot, nout, lerr, ok )
785  nt = nt + 6
786 *
787 * SSBEVD
788 *
789  srnamt = 'SSBEVD'
790  infot = 1
791  CALL ssbevd( '/', 'U', 0, 0, a, 1, x, z, 1, w, 1, iw, 1, info )
792  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
793  infot = 2
794  CALL ssbevd( 'N', '/', 0, 0, a, 1, x, z, 1, w, 1, iw, 1, info )
795  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
796  infot = 3
797  CALL ssbevd( 'N', 'U', -1, 0, a, 1, x, z, 1, w, 1, iw, 1,
798  $ info )
799  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
800  infot = 4
801  CALL ssbevd( 'N', 'U', 0, -1, a, 1, x, z, 1, w, 1, iw, 1,
802  $ info )
803  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
804  infot = 6
805  CALL ssbevd( 'N', 'U', 2, 1, a, 1, x, z, 1, w, 4, iw, 1, info )
806  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
807  infot = 9
808  CALL ssbevd( 'V', 'U', 2, 1, a, 2, x, z, 1, w, 25, iw, 12,
809  $ info )
810  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
811  infot = 11
812  CALL ssbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 0, iw, 1, info )
813  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
814  infot = 11
815  CALL ssbevd( 'N', 'U', 2, 0, a, 1, x, z, 1, w, 3, iw, 1, info )
816  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
817  infot = 11
818  CALL ssbevd( 'V', 'U', 2, 0, a, 1, x, z, 2, w, 18, iw, 12,
819  $ info )
820  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
821  infot = 13
822  CALL ssbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 1, iw, 0, info )
823  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
824  infot = 13
825  CALL ssbevd( 'V', 'U', 2, 0, a, 1, x, z, 2, w, 25, iw, 11,
826  $ info )
827  CALL chkxer( 'SSBEVD', infot, nout, lerr, ok )
828  nt = nt + 11
829 *
830 * SSBEV
831 *
832  srnamt = 'SSBEV '
833  infot = 1
834  CALL ssbev( '/', 'U', 0, 0, a, 1, x, z, 1, w, info )
835  CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
836  infot = 2
837  CALL ssbev( 'N', '/', 0, 0, a, 1, x, z, 1, w, info )
838  CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
839  infot = 3
840  CALL ssbev( 'N', 'U', -1, 0, a, 1, x, z, 1, w, info )
841  CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
842  infot = 4
843  CALL ssbev( 'N', 'U', 0, -1, a, 1, x, z, 1, w, info )
844  CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
845  infot = 6
846  CALL ssbev( 'N', 'U', 2, 1, a, 1, x, z, 1, w, info )
847  CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
848  infot = 9
849  CALL ssbev( 'V', 'U', 2, 0, a, 1, x, z, 1, w, info )
850  CALL chkxer( 'SSBEV ', infot, nout, lerr, ok )
851  nt = nt + 6
852 *
853 * SSBEVX
854 *
855  srnamt = 'SSBEVX'
856  infot = 1
857  CALL ssbevx( '/', 'A', 'U', 0, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
858  $ 0.0, m, x, z, 1, w, iw, i3, info )
859  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
860  infot = 2
861  CALL ssbevx( 'N', '/', 'U', 0, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
862  $ 0.0, m, x, z, 1, w, iw, i3, info )
863  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
864  infot = 3
865  CALL ssbevx( 'N', 'A', '/', 0, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
866  $ 0.0, m, x, z, 1, w, iw, i3, info )
867  infot = 4
868  CALL ssbevx( 'N', 'A', 'U', -1, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
869  $ 0.0, m, x, z, 1, w, iw, i3, info )
870  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
871  infot = 5
872  CALL ssbevx( 'N', 'A', 'U', 0, -1, a, 1, q, 1, 0.0, 0.0, 0, 0,
873  $ 0.0, m, x, z, 1, w, iw, i3, info )
874  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
875  infot = 7
876  CALL ssbevx( 'N', 'A', 'U', 2, 1, a, 1, q, 1, 0.0, 0.0, 0, 0,
877  $ 0.0, m, x, z, 1, w, iw, i3, info )
878  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
879  infot = 9
880  CALL ssbevx( 'V', 'A', 'U', 2, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
881  $ 0.0, m, x, z, 2, w, iw, i3, info )
882  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
883  infot = 11
884  CALL ssbevx( 'N', 'V', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
885  $ 0.0, m, x, z, 1, w, iw, i3, info )
886  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
887  infot = 12
888  CALL ssbevx( 'N', 'I', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
889  $ 0.0, m, x, z, 1, w, iw, i3, info )
890  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
891  infot = 12
892  CALL ssbevx( 'N', 'I', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 2, 1,
893  $ 0.0, m, x, z, 1, w, iw, i3, info )
894  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
895  infot = 13
896  CALL ssbevx( 'N', 'I', 'U', 2, 0, a, 1, q, 1, 0.0, 0.0, 2, 1,
897  $ 0.0, m, x, z, 1, w, iw, i3, info )
898  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
899  infot = 13
900  CALL ssbevx( 'N', 'I', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 1, 2,
901  $ 0.0, m, x, z, 1, w, iw, i3, info )
902  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
903  infot = 18
904  CALL ssbevx( 'V', 'A', 'U', 2, 0, a, 1, q, 2, 0.0, 0.0, 0, 0,
905  $ 0.0, m, x, z, 1, w, iw, i3, info )
906  CALL chkxer( 'SSBEVX', infot, nout, lerr, ok )
907  nt = nt + 13
908  END IF
909 *
910 * Print a summary line.
911 *
912  IF( ok ) THEN
913  WRITE( nout, fmt = 9999 )path, nt
914  ELSE
915  WRITE( nout, fmt = 9998 )path
916  END IF
917 *
918  9999 FORMAT( 1x, a3, ' routines passed the tests of the error exits',
919  $ ' (', i3, ' tests done)' )
920  9998 FORMAT( ' *** ', a3, ' routines failed the tests of the error ',
921  $ 'exits ***' )
922 *
923  RETURN
924 *
925 * End of SERRST
926 *
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 ssyevr(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, ISUPPZ, WORK, LWORK, IWORK, LIWORK, INFO)
SSYEVR computes the eigenvalues and, optionally, the left and/or right eigenvectors for SY matrices ...
Definition: ssyevr.f:336
subroutine 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 sstein(N, D, E, M, W, IBLOCK, ISPLIT, Z, LDZ, WORK, IWORK, IFAIL, INFO)
SSTEIN
Definition: sstein.f:176
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 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
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
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 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 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 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 sopgtr(UPLO, N, AP, TAU, Q, LDQ, WORK, INFO)
SOPGTR
Definition: sopgtr.f:116
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 ssteqr(COMPZ, N, D, E, Z, LDZ, WORK, INFO)
SSTEQR
Definition: ssteqr.f:133
subroutine sopmtr(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK, INFO)
SOPMTR
Definition: sopmtr.f:152
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 sorgtr(UPLO, N, A, LDA, TAU, WORK, LWORK, INFO)
SORGTR
Definition: sorgtr.f:125
subroutine spteqr(COMPZ, N, D, E, Z, LDZ, WORK, INFO)
SPTEQR
Definition: spteqr.f:147
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 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 ssbtrd(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ, WORK, INFO)
SSBTRD
Definition: ssbtrd.f:165
subroutine ssterf(N, D, E, INFO)
SSTERF
Definition: ssterf.f:88
subroutine sormtr(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
SORMTR
Definition: sormtr.f:174
subroutine sstedc(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, IWORK, LIWORK, INFO)
SSTEDC
Definition: sstedc.f:190
subroutine ssptrd(UPLO, N, AP, D, E, TAU, INFO)
SSPTRD
Definition: ssptrd.f:152
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 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 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

Here is the call graph for this function:

Here is the caller graph for this function: