LAPACK  3.6.1
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 *> \endverbatim
29 *
30 * Arguments:
31 * ==========
32 *
33 *> \param[in] PATH
34 *> \verbatim
35 *> PATH is CHARACTER*3
36 *> The LAPACK path name for the routines to be tested.
37 *> \endverbatim
38 *>
39 *> \param[in] NUNIT
40 *> \verbatim
41 *> NUNIT is INTEGER
42 *> The unit number for output.
43 *> \endverbatim
44 *
45 * Authors:
46 * ========
47 *
48 *> \author Univ. of Tennessee
49 *> \author Univ. of California Berkeley
50 *> \author Univ. of Colorado Denver
51 *> \author NAG Ltd.
52 *
53 *> \date November 2011
54 *
55 *> \ingroup complex_eig
56 *
57 * =====================================================================
58  SUBROUTINE cerrst( PATH, NUNIT )
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 * .. Parameters ..
73  INTEGER NMAX, LIW, LW
74  parameter ( nmax = 3, liw = 12*nmax, lw = 20*nmax )
75 * ..
76 * .. Local Scalars ..
77  CHARACTER*2 C2
78  INTEGER I, INFO, J, M, N, NT
79 * ..
80 * .. Local Arrays ..
81  INTEGER I1( nmax ), I2( nmax ), I3( nmax ), IW( liw )
82  REAL D( nmax ), E( nmax ), R( lw ), RW( lw ),
83  $ x( nmax )
84  COMPLEX A( nmax, nmax ), C( nmax, nmax ),
85  $ q( nmax, nmax ), tau( nmax ), w( lw ),
86  $ z( nmax, nmax )
87 * ..
88 * .. External Functions ..
89  LOGICAL LSAMEN
90  EXTERNAL lsamen
91 * ..
92 * .. External Subroutines ..
93  EXTERNAL chbev, chbevd, chbevx, chbtrd, cheev, cheevd,
97 * ..
98 * .. Scalars in Common ..
99  LOGICAL LERR, OK
100  CHARACTER*32 SRNAMT
101  INTEGER INFOT, NOUT
102 * ..
103 * .. Common blocks ..
104  COMMON / infoc / infot, nout, ok, lerr
105  COMMON / srnamc / srnamt
106 * ..
107 * .. Intrinsic Functions ..
108  INTRINSIC real
109 * ..
110 * .. Executable Statements ..
111 *
112  nout = nunit
113  WRITE( nout, fmt = * )
114  c2 = path( 2: 3 )
115 *
116 * Set the variables to innocuous values.
117 *
118  DO 20 j = 1, nmax
119  DO 10 i = 1, nmax
120  a( i, j ) = 1. / REAL( i+j )
121  10 CONTINUE
122  20 CONTINUE
123  DO 30 j = 1, nmax
124  d( j ) = REAL( j )
125  e( j ) = 0.0
126  i1( j ) = j
127  i2( j ) = j
128  tau( j ) = 1.
129  30 CONTINUE
130  ok = .true.
131  nt = 0
132 *
133 * Test error exits for the ST path.
134 *
135  IF( lsamen( 2, c2, 'ST' ) ) THEN
136 *
137 * CHETRD
138 *
139  srnamt = 'CHETRD'
140  infot = 1
141  CALL chetrd( '/', 0, a, 1, d, e, tau, w, 1, info )
142  CALL chkxer( 'CHETRD', infot, nout, lerr, ok )
143  infot = 2
144  CALL chetrd( 'U', -1, a, 1, d, e, tau, w, 1, info )
145  CALL chkxer( 'CHETRD', infot, nout, lerr, ok )
146  infot = 4
147  CALL chetrd( 'U', 2, a, 1, d, e, tau, w, 1, info )
148  CALL chkxer( 'CHETRD', infot, nout, lerr, ok )
149  infot = 9
150  CALL chetrd( 'U', 0, a, 1, d, e, tau, w, 0, info )
151  CALL chkxer( 'CHETRD', infot, nout, lerr, ok )
152  nt = nt + 4
153 *
154 * CUNGTR
155 *
156  srnamt = 'CUNGTR'
157  infot = 1
158  CALL cungtr( '/', 0, a, 1, tau, w, 1, info )
159  CALL chkxer( 'CUNGTR', infot, nout, lerr, ok )
160  infot = 2
161  CALL cungtr( 'U', -1, a, 1, tau, w, 1, info )
162  CALL chkxer( 'CUNGTR', infot, nout, lerr, ok )
163  infot = 4
164  CALL cungtr( 'U', 2, a, 1, tau, w, 1, info )
165  CALL chkxer( 'CUNGTR', infot, nout, lerr, ok )
166  infot = 7
167  CALL cungtr( 'U', 3, a, 3, tau, w, 1, info )
168  CALL chkxer( 'CUNGTR', infot, nout, lerr, ok )
169  nt = nt + 4
170 *
171 * CUNMTR
172 *
173  srnamt = 'CUNMTR'
174  infot = 1
175  CALL cunmtr( '/', 'U', 'N', 0, 0, a, 1, tau, c, 1, w, 1, info )
176  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
177  infot = 2
178  CALL cunmtr( 'L', '/', 'N', 0, 0, a, 1, tau, c, 1, w, 1, info )
179  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
180  infot = 3
181  CALL cunmtr( 'L', 'U', '/', 0, 0, a, 1, tau, c, 1, w, 1, info )
182  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
183  infot = 4
184  CALL cunmtr( 'L', 'U', 'N', -1, 0, a, 1, tau, c, 1, w, 1,
185  $ info )
186  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
187  infot = 5
188  CALL cunmtr( 'L', 'U', 'N', 0, -1, a, 1, tau, c, 1, w, 1,
189  $ info )
190  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
191  infot = 7
192  CALL cunmtr( 'L', 'U', 'N', 2, 0, a, 1, tau, c, 2, w, 1, info )
193  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
194  infot = 7
195  CALL cunmtr( 'R', 'U', 'N', 0, 2, a, 1, tau, c, 1, w, 1, info )
196  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
197  infot = 10
198  CALL cunmtr( 'L', 'U', 'N', 2, 0, a, 2, tau, c, 1, w, 1, info )
199  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
200  infot = 12
201  CALL cunmtr( 'L', 'U', 'N', 0, 2, a, 1, tau, c, 1, w, 1, info )
202  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
203  infot = 12
204  CALL cunmtr( 'R', 'U', 'N', 2, 0, a, 1, tau, c, 2, w, 1, info )
205  CALL chkxer( 'CUNMTR', infot, nout, lerr, ok )
206  nt = nt + 10
207 *
208 * CHPTRD
209 *
210  srnamt = 'CHPTRD'
211  infot = 1
212  CALL chptrd( '/', 0, a, d, e, tau, info )
213  CALL chkxer( 'CHPTRD', infot, nout, lerr, ok )
214  infot = 2
215  CALL chptrd( 'U', -1, a, d, e, tau, info )
216  CALL chkxer( 'CHPTRD', infot, nout, lerr, ok )
217  nt = nt + 2
218 *
219 * CUPGTR
220 *
221  srnamt = 'CUPGTR'
222  infot = 1
223  CALL cupgtr( '/', 0, a, tau, z, 1, w, info )
224  CALL chkxer( 'CUPGTR', infot, nout, lerr, ok )
225  infot = 2
226  CALL cupgtr( 'U', -1, a, tau, z, 1, w, info )
227  CALL chkxer( 'CUPGTR', infot, nout, lerr, ok )
228  infot = 6
229  CALL cupgtr( 'U', 2, a, tau, z, 1, w, info )
230  CALL chkxer( 'CUPGTR', infot, nout, lerr, ok )
231  nt = nt + 3
232 *
233 * CUPMTR
234 *
235  srnamt = 'CUPMTR'
236  infot = 1
237  CALL cupmtr( '/', 'U', 'N', 0, 0, a, tau, c, 1, w, info )
238  CALL chkxer( 'CUPMTR', infot, nout, lerr, ok )
239  infot = 2
240  CALL cupmtr( 'L', '/', 'N', 0, 0, a, tau, c, 1, w, info )
241  CALL chkxer( 'CUPMTR', infot, nout, lerr, ok )
242  infot = 3
243  CALL cupmtr( 'L', 'U', '/', 0, 0, a, tau, c, 1, w, info )
244  CALL chkxer( 'CUPMTR', infot, nout, lerr, ok )
245  infot = 4
246  CALL cupmtr( 'L', 'U', 'N', -1, 0, a, tau, c, 1, w, info )
247  CALL chkxer( 'CUPMTR', infot, nout, lerr, ok )
248  infot = 5
249  CALL cupmtr( 'L', 'U', 'N', 0, -1, a, tau, c, 1, w, info )
250  CALL chkxer( 'CUPMTR', infot, nout, lerr, ok )
251  infot = 9
252  CALL cupmtr( 'L', 'U', 'N', 2, 0, a, tau, c, 1, w, info )
253  CALL chkxer( 'CUPMTR', infot, nout, lerr, ok )
254  nt = nt + 6
255 *
256 * CPTEQR
257 *
258  srnamt = 'CPTEQR'
259  infot = 1
260  CALL cpteqr( '/', 0, d, e, z, 1, rw, info )
261  CALL chkxer( 'CPTEQR', infot, nout, lerr, ok )
262  infot = 2
263  CALL cpteqr( 'N', -1, d, e, z, 1, rw, info )
264  CALL chkxer( 'CPTEQR', infot, nout, lerr, ok )
265  infot = 6
266  CALL cpteqr( 'V', 2, d, e, z, 1, rw, info )
267  CALL chkxer( 'CPTEQR', infot, nout, lerr, ok )
268  nt = nt + 3
269 *
270 * CSTEIN
271 *
272  srnamt = 'CSTEIN'
273  infot = 1
274  CALL cstein( -1, d, e, 0, x, i1, i2, z, 1, rw, iw, i3, info )
275  CALL chkxer( 'CSTEIN', infot, nout, lerr, ok )
276  infot = 4
277  CALL cstein( 0, d, e, -1, x, i1, i2, z, 1, rw, iw, i3, info )
278  CALL chkxer( 'CSTEIN', infot, nout, lerr, ok )
279  infot = 4
280  CALL cstein( 0, d, e, 1, x, i1, i2, z, 1, rw, iw, i3, info )
281  CALL chkxer( 'CSTEIN', infot, nout, lerr, ok )
282  infot = 9
283  CALL cstein( 2, d, e, 0, x, i1, i2, z, 1, rw, iw, i3, info )
284  CALL chkxer( 'CSTEIN', infot, nout, lerr, ok )
285  nt = nt + 4
286 *
287 * CSTEQR
288 *
289  srnamt = 'CSTEQR'
290  infot = 1
291  CALL csteqr( '/', 0, d, e, z, 1, rw, info )
292  CALL chkxer( 'CSTEQR', infot, nout, lerr, ok )
293  infot = 2
294  CALL csteqr( 'N', -1, d, e, z, 1, rw, info )
295  CALL chkxer( 'CSTEQR', infot, nout, lerr, ok )
296  infot = 6
297  CALL csteqr( 'V', 2, d, e, z, 1, rw, info )
298  CALL chkxer( 'CSTEQR', infot, nout, lerr, ok )
299  nt = nt + 3
300 *
301 * CSTEDC
302 *
303  srnamt = 'CSTEDC'
304  infot = 1
305  CALL cstedc( '/', 0, d, e, z, 1, w, 1, rw, 1, iw, 1, info )
306  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
307  infot = 2
308  CALL cstedc( 'N', -1, d, e, z, 1, w, 1, rw, 1, iw, 1, info )
309  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
310  infot = 6
311  CALL cstedc( 'V', 2, d, e, z, 1, w, 4, rw, 23, iw, 28, info )
312  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
313  infot = 8
314  CALL cstedc( 'N', 2, d, e, z, 1, w, 0, rw, 1, iw, 1, info )
315  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
316  infot = 8
317  CALL cstedc( 'V', 2, d, e, z, 2, w, 0, rw, 23, iw, 28, info )
318  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
319  infot = 10
320  CALL cstedc( 'N', 2, d, e, z, 1, w, 1, rw, 0, iw, 1, info )
321  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
322  infot = 10
323  CALL cstedc( 'I', 2, d, e, z, 2, w, 1, rw, 1, iw, 12, info )
324  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
325  infot = 10
326  CALL cstedc( 'V', 2, d, e, z, 2, w, 4, rw, 1, iw, 28, info )
327  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
328  infot = 12
329  CALL cstedc( 'N', 2, d, e, z, 1, w, 1, rw, 1, iw, 0, info )
330  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
331  infot = 12
332  CALL cstedc( 'I', 2, d, e, z, 2, w, 1, rw, 23, iw, 0, info )
333  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
334  infot = 12
335  CALL cstedc( 'V', 2, d, e, z, 2, w, 4, rw, 23, iw, 0, info )
336  CALL chkxer( 'CSTEDC', infot, nout, lerr, ok )
337  nt = nt + 11
338 *
339 * CHEEVD
340 *
341  srnamt = 'CHEEVD'
342  infot = 1
343  CALL cheevd( '/', 'U', 0, a, 1, x, w, 1, rw, 1, iw, 1, info )
344  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
345  infot = 2
346  CALL cheevd( 'N', '/', 0, a, 1, x, w, 1, rw, 1, iw, 1, info )
347  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
348  infot = 3
349  CALL cheevd( 'N', 'U', -1, a, 1, x, w, 1, rw, 1, iw, 1, info )
350  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
351  infot = 5
352  CALL cheevd( 'N', 'U', 2, a, 1, x, w, 3, rw, 2, iw, 1, info )
353  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
354  infot = 8
355  CALL cheevd( 'N', 'U', 1, a, 1, x, w, 0, rw, 1, iw, 1, info )
356  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
357  infot = 8
358  CALL cheevd( 'N', 'U', 2, a, 2, x, w, 2, rw, 2, iw, 1, info )
359  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
360  infot = 8
361  CALL cheevd( 'V', 'U', 2, a, 2, x, w, 3, rw, 25, iw, 12, info )
362  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
363  infot = 10
364  CALL cheevd( 'N', 'U', 1, a, 1, x, w, 1, rw, 0, iw, 1, info )
365  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
366  infot = 10
367  CALL cheevd( 'N', 'U', 2, a, 2, x, w, 3, rw, 1, iw, 1, info )
368  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
369  infot = 10
370  CALL cheevd( 'V', 'U', 2, a, 2, x, w, 8, rw, 18, iw, 12, info )
371  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
372  infot = 12
373  CALL cheevd( 'N', 'U', 1, a, 1, x, w, 1, rw, 1, iw, 0, info )
374  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
375  infot = 12
376  CALL cheevd( 'V', 'U', 2, a, 2, x, w, 8, rw, 25, iw, 11, info )
377  CALL chkxer( 'CHEEVD', infot, nout, lerr, ok )
378  nt = nt + 12
379 *
380 * CHEEV
381 *
382  srnamt = 'CHEEV '
383  infot = 1
384  CALL cheev( '/', 'U', 0, a, 1, x, w, 1, rw, info )
385  CALL chkxer( 'CHEEV ', infot, nout, lerr, ok )
386  infot = 2
387  CALL cheev( 'N', '/', 0, a, 1, x, w, 1, rw, info )
388  CALL chkxer( 'CHEEV ', infot, nout, lerr, ok )
389  infot = 3
390  CALL cheev( 'N', 'U', -1, a, 1, x, w, 1, rw, info )
391  CALL chkxer( 'CHEEV ', infot, nout, lerr, ok )
392  infot = 5
393  CALL cheev( 'N', 'U', 2, a, 1, x, w, 3, rw, info )
394  CALL chkxer( 'CHEEV ', infot, nout, lerr, ok )
395  infot = 8
396  CALL cheev( 'N', 'U', 2, a, 2, x, w, 2, rw, info )
397  CALL chkxer( 'CHEEV ', infot, nout, lerr, ok )
398  nt = nt + 5
399 *
400 * CHEEVX
401 *
402  srnamt = 'CHEEVX'
403  infot = 1
404  CALL cheevx( '/', 'A', 'U', 0, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
405  $ z, 1, w, 1, rw, iw, i3, info )
406  CALL chkxer( 'CHEEVX', infot, nout, lerr, ok )
407  infot = 2
408  CALL cheevx( 'V', '/', 'U', 0, a, 1, 0.0, 1.0, 1, 0, 0.0, m, x,
409  $ z, 1, w, 1, rw, iw, i3, info )
410  CALL chkxer( 'CHEEVX', infot, nout, lerr, ok )
411  infot = 3
412  CALL cheevx( 'V', 'A', '/', 0, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
413  $ z, 1, w, 1, rw, iw, i3, info )
414  infot = 4
415  CALL cheevx( 'V', 'A', 'U', -1, a, 1, 0.0, 0.0, 0, 0, 0.0, m,
416  $ x, z, 1, w, 1, rw, iw, i3, info )
417  CALL chkxer( 'CHEEVX', infot, nout, lerr, ok )
418  infot = 6
419  CALL cheevx( 'V', 'A', 'U', 2, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
420  $ z, 2, w, 3, rw, iw, i3, info )
421  CALL chkxer( 'CHEEVX', infot, nout, lerr, ok )
422  infot = 8
423  CALL cheevx( 'V', 'V', 'U', 1, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
424  $ z, 1, w, 1, rw, iw, i3, info )
425  CALL chkxer( 'CHEEVX', infot, nout, lerr, ok )
426  infot = 9
427  CALL cheevx( 'V', 'I', 'U', 1, a, 1, 0.0, 0.0, 0, 0, 0.0, m, x,
428  $ z, 1, w, 1, rw, iw, i3, info )
429  CALL chkxer( 'CHEEVX', infot, nout, lerr, ok )
430  infot = 10
431  CALL cheevx( 'V', 'I', 'U', 2, a, 2, 0.0, 0.0, 2, 1, 0.0, m, x,
432  $ z, 2, w, 3, rw, iw, i3, info )
433  CALL chkxer( 'CHEEVX', infot, nout, lerr, ok )
434  infot = 15
435  CALL cheevx( 'V', 'A', 'U', 2, a, 2, 0.0, 0.0, 0, 0, 0.0, m, x,
436  $ z, 1, w, 3, rw, iw, i3, info )
437  CALL chkxer( 'CHEEVX', infot, nout, lerr, ok )
438  infot = 17
439  CALL cheevx( 'V', 'A', 'U', 2, a, 2, 0.0, 0.0, 0, 0, 0.0, m, x,
440  $ z, 2, w, 2, rw, iw, i1, info )
441  CALL chkxer( 'CHEEVX', infot, nout, lerr, ok )
442  nt = nt + 10
443 *
444 * CHEEVR
445 *
446  srnamt = 'CHEEVR'
447  n = 1
448  infot = 1
449  CALL cheevr( '/', 'A', 'U', 0, a, 1, 0.0, 0.0, 1, 1, 0.0, m, r,
450  $ z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ), 10*n,
451  $ info )
452  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
453  infot = 2
454  CALL cheevr( 'V', '/', 'U', 0, a, 1, 0.0, 0.0, 1, 1, 0.0, m, r,
455  $ z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ), 10*n,
456  $ info )
457  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
458  infot = 3
459  CALL cheevr( 'V', 'A', '/', -1, a, 1, 0.0, 0.0, 1, 1, 0.0, m,
460  $ r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ), 10*n,
461  $ info )
462  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
463  infot = 4
464  CALL cheevr( 'V', 'A', 'U', -1, a, 1, 0.0, 0.0, 1, 1, 0.0, m,
465  $ r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ), 10*n,
466  $ info )
467  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
468  infot = 6
469  CALL cheevr( 'V', 'A', 'U', 2, a, 1, 0.0, 0.0, 1, 1, 0.0, m, r,
470  $ z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ), 10*n,
471  $ info )
472  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
473  infot = 8
474  CALL cheevr( 'V', 'V', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
475  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
476  $ 10*n, info )
477  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
478  infot = 9
479  CALL cheevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 0, 1, 0.0,
480  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
481  $ 10*n, info )
482  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
483  infot = 10
484 *
485  CALL cheevr( 'V', 'I', 'U', 2, a, 2, 0.0e0, 0.0e0, 2, 1, 0.0,
486  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
487  $ 10*n, info )
488  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
489  infot = 15
490  CALL cheevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
491  $ m, r, z, 0, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
492  $ 10*n, info )
493  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
494  infot = 18
495  CALL cheevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
496  $ m, r, z, 1, iw, q, 2*n-1, rw, 24*n, iw( 2*n+1 ),
497  $ 10*n, info )
498  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
499  infot = 20
500  CALL cheevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
501  $ m, r, z, 1, iw, q, 2*n, rw, 24*n-1, iw( 2*n-1 ),
502  $ 10*n, info )
503  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
504  infot = 22
505  CALL cheevr( 'V', 'I', 'U', 1, a, 1, 0.0e0, 0.0e0, 1, 1, 0.0,
506  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw, 10*n-1,
507  $ info )
508  CALL chkxer( 'CHEEVR', infot, nout, lerr, ok )
509  nt = nt + 12
510 *
511 * CHPEVD
512 *
513  srnamt = 'CHPEVD'
514  infot = 1
515  CALL chpevd( '/', 'U', 0, a, x, z, 1, w, 1, rw, 1, iw, 1,
516  $ info )
517  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
518  infot = 2
519  CALL chpevd( 'N', '/', 0, a, x, z, 1, w, 1, rw, 1, iw, 1,
520  $ info )
521  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
522  infot = 3
523  CALL chpevd( 'N', 'U', -1, a, x, z, 1, w, 1, rw, 1, iw, 1,
524  $ info )
525  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
526  infot = 7
527  CALL chpevd( 'V', 'U', 2, a, x, z, 1, w, 4, rw, 25, iw, 12,
528  $ info )
529  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
530  infot = 9
531  CALL chpevd( 'N', 'U', 1, a, x, z, 1, w, 0, rw, 1, iw, 1,
532  $ info )
533  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
534  infot = 9
535  CALL chpevd( 'N', 'U', 2, a, x, z, 2, w, 1, rw, 2, iw, 1,
536  $ info )
537  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
538  infot = 9
539  CALL chpevd( 'V', 'U', 2, a, x, z, 2, w, 2, rw, 25, iw, 12,
540  $ info )
541  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
542  infot = 11
543  CALL chpevd( 'N', 'U', 1, a, x, z, 1, w, 1, rw, 0, iw, 1,
544  $ info )
545  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
546  infot = 11
547  CALL chpevd( 'N', 'U', 2, a, x, z, 2, w, 2, rw, 1, iw, 1,
548  $ info )
549  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
550  infot = 11
551  CALL chpevd( 'V', 'U', 2, a, x, z, 2, w, 4, rw, 18, iw, 12,
552  $ info )
553  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
554  infot = 13
555  CALL chpevd( 'N', 'U', 1, a, x, z, 1, w, 1, rw, 1, iw, 0,
556  $ info )
557  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
558  infot = 13
559  CALL chpevd( 'N', 'U', 2, a, x, z, 2, w, 2, rw, 2, iw, 0,
560  $ info )
561  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
562  infot = 13
563  CALL chpevd( 'V', 'U', 2, a, x, z, 2, w, 4, rw, 25, iw, 2,
564  $ info )
565  CALL chkxer( 'CHPEVD', infot, nout, lerr, ok )
566  nt = nt + 13
567 *
568 * CHPEV
569 *
570  srnamt = 'CHPEV '
571  infot = 1
572  CALL chpev( '/', 'U', 0, a, x, z, 1, w, rw, info )
573  CALL chkxer( 'CHPEV ', infot, nout, lerr, ok )
574  infot = 2
575  CALL chpev( 'N', '/', 0, a, x, z, 1, w, rw, info )
576  CALL chkxer( 'CHPEV ', infot, nout, lerr, ok )
577  infot = 3
578  CALL chpev( 'N', 'U', -1, a, x, z, 1, w, rw, info )
579  CALL chkxer( 'CHPEV ', infot, nout, lerr, ok )
580  infot = 7
581  CALL chpev( 'V', 'U', 2, a, x, z, 1, w, rw, info )
582  CALL chkxer( 'CHPEV ', infot, nout, lerr, ok )
583  nt = nt + 4
584 *
585 * CHPEVX
586 *
587  srnamt = 'CHPEVX'
588  infot = 1
589  CALL chpevx( '/', 'A', 'U', 0, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
590  $ 1, w, rw, iw, i3, info )
591  CALL chkxer( 'CHPEVX', infot, nout, lerr, ok )
592  infot = 2
593  CALL chpevx( 'V', '/', 'U', 0, a, 0.0, 1.0, 1, 0, 0.0, m, x, z,
594  $ 1, w, rw, iw, i3, info )
595  CALL chkxer( 'CHPEVX', infot, nout, lerr, ok )
596  infot = 3
597  CALL chpevx( 'V', 'A', '/', 0, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
598  $ 1, w, rw, iw, i3, info )
599  CALL chkxer( 'CHPEVX', infot, nout, lerr, ok )
600  infot = 4
601  CALL chpevx( 'V', 'A', 'U', -1, a, 0.0, 0.0, 0, 0, 0.0, m, x,
602  $ z, 1, w, rw, iw, i3, info )
603  CALL chkxer( 'CHPEVX', infot, nout, lerr, ok )
604  infot = 7
605  CALL chpevx( 'V', 'V', 'U', 1, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
606  $ 1, w, rw, iw, i3, info )
607  CALL chkxer( 'CHPEVX', infot, nout, lerr, ok )
608  infot = 8
609  CALL chpevx( 'V', 'I', 'U', 1, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
610  $ 1, w, rw, iw, i3, info )
611  CALL chkxer( 'CHPEVX', infot, nout, lerr, ok )
612  infot = 9
613  CALL chpevx( 'V', 'I', 'U', 2, a, 0.0, 0.0, 2, 1, 0.0, m, x, z,
614  $ 2, w, rw, iw, i3, info )
615  CALL chkxer( 'CHPEVX', infot, nout, lerr, ok )
616  infot = 14
617  CALL chpevx( 'V', 'A', 'U', 2, a, 0.0, 0.0, 0, 0, 0.0, m, x, z,
618  $ 1, w, rw, iw, i3, info )
619  CALL chkxer( 'CHPEVX', infot, nout, lerr, ok )
620  nt = nt + 8
621 *
622 * Test error exits for the HB path.
623 *
624  ELSE IF( lsamen( 2, c2, 'HB' ) ) THEN
625 *
626 * CHBTRD
627 *
628  srnamt = 'CHBTRD'
629  infot = 1
630  CALL chbtrd( '/', 'U', 0, 0, a, 1, d, e, z, 1, w, info )
631  CALL chkxer( 'CHBTRD', infot, nout, lerr, ok )
632  infot = 2
633  CALL chbtrd( 'N', '/', 0, 0, a, 1, d, e, z, 1, w, info )
634  CALL chkxer( 'CHBTRD', infot, nout, lerr, ok )
635  infot = 3
636  CALL chbtrd( 'N', 'U', -1, 0, a, 1, d, e, z, 1, w, info )
637  CALL chkxer( 'CHBTRD', infot, nout, lerr, ok )
638  infot = 4
639  CALL chbtrd( 'N', 'U', 0, -1, a, 1, d, e, z, 1, w, info )
640  CALL chkxer( 'CHBTRD', infot, nout, lerr, ok )
641  infot = 6
642  CALL chbtrd( 'N', 'U', 1, 1, a, 1, d, e, z, 1, w, info )
643  CALL chkxer( 'CHBTRD', infot, nout, lerr, ok )
644  infot = 10
645  CALL chbtrd( 'V', 'U', 2, 0, a, 1, d, e, z, 1, w, info )
646  CALL chkxer( 'CHBTRD', infot, nout, lerr, ok )
647  nt = nt + 6
648 *
649 * CHBEVD
650 *
651  srnamt = 'CHBEVD'
652  infot = 1
653  CALL chbevd( '/', 'U', 0, 0, a, 1, x, z, 1, w, 1, rw, 1, iw, 1,
654  $ info )
655  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
656  infot = 2
657  CALL chbevd( 'N', '/', 0, 0, a, 1, x, z, 1, w, 1, rw, 1, iw, 1,
658  $ info )
659  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
660  infot = 3
661  CALL chbevd( 'N', 'U', -1, 0, a, 1, x, z, 1, w, 1, rw, 1, iw,
662  $ 1, info )
663  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
664  infot = 4
665  CALL chbevd( 'N', 'U', 0, -1, a, 1, x, z, 1, w, 1, rw, 1, iw,
666  $ 1, info )
667  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
668  infot = 6
669  CALL chbevd( 'N', 'U', 2, 1, a, 1, x, z, 1, w, 2, rw, 2, iw, 1,
670  $ info )
671  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
672  infot = 9
673  CALL chbevd( 'V', 'U', 2, 1, a, 2, x, z, 1, w, 8, rw, 25, iw,
674  $ 12, info )
675  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
676  infot = 11
677  CALL chbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 0, rw, 1, iw, 1,
678  $ info )
679  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
680  infot = 11
681  CALL chbevd( 'N', 'U', 2, 1, a, 2, x, z, 2, w, 1, rw, 2, iw, 1,
682  $ info )
683  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
684  infot = 11
685  CALL chbevd( 'V', 'U', 2, 1, a, 2, x, z, 2, w, 2, rw, 25, iw,
686  $ 12, info )
687  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
688  infot = 13
689  CALL chbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 1, rw, 0, iw, 1,
690  $ info )
691  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
692  infot = 13
693  CALL chbevd( 'N', 'U', 2, 1, a, 2, x, z, 2, w, 2, rw, 1, iw, 1,
694  $ info )
695  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
696  infot = 13
697  CALL chbevd( 'V', 'U', 2, 1, a, 2, x, z, 2, w, 8, rw, 2, iw,
698  $ 12, info )
699  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
700  infot = 15
701  CALL chbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 1, rw, 1, iw, 0,
702  $ info )
703  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
704  infot = 15
705  CALL chbevd( 'N', 'U', 2, 1, a, 2, x, z, 2, w, 2, rw, 2, iw, 0,
706  $ info )
707  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
708  infot = 15
709  CALL chbevd( 'V', 'U', 2, 1, a, 2, x, z, 2, w, 8, rw, 25, iw,
710  $ 2, info )
711  CALL chkxer( 'CHBEVD', infot, nout, lerr, ok )
712  nt = nt + 15
713 *
714 * CHBEV
715 *
716  srnamt = 'CHBEV '
717  infot = 1
718  CALL chbev( '/', 'U', 0, 0, a, 1, x, z, 1, w, rw, info )
719  CALL chkxer( 'CHBEV ', infot, nout, lerr, ok )
720  infot = 2
721  CALL chbev( 'N', '/', 0, 0, a, 1, x, z, 1, w, rw, info )
722  CALL chkxer( 'CHBEV ', infot, nout, lerr, ok )
723  infot = 3
724  CALL chbev( 'N', 'U', -1, 0, a, 1, x, z, 1, w, rw, info )
725  CALL chkxer( 'CHBEV ', infot, nout, lerr, ok )
726  infot = 4
727  CALL chbev( 'N', 'U', 0, -1, a, 1, x, z, 1, w, rw, info )
728  CALL chkxer( 'CHBEV ', infot, nout, lerr, ok )
729  infot = 6
730  CALL chbev( 'N', 'U', 2, 1, a, 1, x, z, 1, w, rw, info )
731  CALL chkxer( 'CHBEV ', infot, nout, lerr, ok )
732  infot = 9
733  CALL chbev( 'V', 'U', 2, 0, a, 1, x, z, 1, w, rw, info )
734  CALL chkxer( 'CHBEV ', infot, nout, lerr, ok )
735  nt = nt + 6
736 *
737 * CHBEVX
738 *
739  srnamt = 'CHBEVX'
740  infot = 1
741  CALL chbevx( '/', 'A', 'U', 0, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
742  $ 0.0, m, x, z, 1, w, rw, iw, i3, info )
743  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
744  infot = 2
745  CALL chbevx( 'V', '/', 'U', 0, 0, a, 1, q, 1, 0.0, 1.0, 1, 0,
746  $ 0.0, m, x, z, 1, w, rw, iw, i3, info )
747  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
748  infot = 3
749  CALL chbevx( 'V', 'A', '/', 0, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
750  $ 0.0, m, x, z, 1, w, rw, iw, i3, info )
751  infot = 4
752  CALL chbevx( 'V', 'A', 'U', -1, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
753  $ 0.0, m, x, z, 1, w, rw, iw, i3, info )
754  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
755  infot = 5
756  CALL chbevx( 'V', 'A', 'U', 0, -1, a, 1, q, 1, 0.0, 0.0, 0, 0,
757  $ 0.0, m, x, z, 1, w, rw, iw, i3, info )
758  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
759  infot = 7
760  CALL chbevx( 'V', 'A', 'U', 2, 1, a, 1, q, 2, 0.0, 0.0, 0, 0,
761  $ 0.0, m, x, z, 2, w, rw, iw, i3, info )
762  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
763  infot = 9
764  CALL chbevx( 'V', 'A', 'U', 2, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
765  $ 0.0, m, x, z, 2, w, rw, iw, i3, info )
766  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
767  infot = 11
768  CALL chbevx( 'V', 'V', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
769  $ 0.0, m, x, z, 1, w, rw, iw, i3, info )
770  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
771  infot = 12
772  CALL chbevx( 'V', 'I', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 0, 0,
773  $ 0.0, m, x, z, 1, w, rw, iw, i3, info )
774  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
775  infot = 13
776  CALL chbevx( 'V', 'I', 'U', 1, 0, a, 1, q, 1, 0.0, 0.0, 1, 2,
777  $ 0.0, m, x, z, 1, w, rw, iw, i3, info )
778  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
779  infot = 18
780  CALL chbevx( 'V', 'A', 'U', 2, 0, a, 1, q, 2, 0.0, 0.0, 0, 0,
781  $ 0.0, m, x, z, 1, w, rw, iw, i3, info )
782  CALL chkxer( 'CHBEVX', infot, nout, lerr, ok )
783  nt = nt + 11
784  END IF
785 *
786 * Print a summary line.
787 *
788  IF( ok ) THEN
789  WRITE( nout, fmt = 9999 )path, nt
790  ELSE
791  WRITE( nout, fmt = 9998 )path
792  END IF
793 *
794  9999 FORMAT( 1x, a3, ' routines passed the tests of the error exits',
795  $ ' (', i3, ' tests done)' )
796  9998 FORMAT( ' *** ', a3, ' routines failed the tests of the error ',
797  $ 'exits ***' )
798 *
799  RETURN
800 *
801 * End of CERRST
802 *
803  END
subroutine cpteqr(COMPZ, N, D, E, Z, LDZ, WORK, INFO)
CPTEQR
Definition: cpteqr.f:147
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 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 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:357
subroutine cupgtr(UPLO, N, AP, TAU, Q, LDQ, WORK, INFO)
CUPGTR
Definition: cupgtr.f:116
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 chbtrd(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ, WORK, INFO)
CHBTRD
Definition: chbtrd.f:165
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine csteqr(COMPZ, N, D, E, Z, LDZ, WORK, INFO)
CSTEQR
Definition: csteqr.f:134
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 cstein(N, D, E, M, W, IBLOCK, ISPLIT, Z, LDZ, WORK, IWORK, IFAIL, INFO)
CSTEIN
Definition: cstein.f:184
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 chetrd(UPLO, N, A, LDA, D, E, TAU, WORK, LWORK, INFO)
CHETRD
Definition: chetrd.f:194
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 cstedc(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)
CSTEDC
Definition: cstedc.f:214
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 chptrd(UPLO, N, AP, D, E, TAU, INFO)
CHPTRD
Definition: chptrd.f:153
subroutine cungtr(UPLO, N, A, LDA, TAU, WORK, LWORK, INFO)
CUNGTR
Definition: cungtr.f:125
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 cupmtr(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK, INFO)
CUPMTR
Definition: cupmtr.f:152
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 cerrst(PATH, NUNIT)
CERRST
Definition: cerrst.f:59