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