LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zerrst.f
Go to the documentation of this file.
1 *> \brief \b ZERRST
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 ZERRST( 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 *> ZERRST tests the error exits for ZHETRD, ZUNGTR, CUNMTR, ZHPTRD,
25 *> ZUNGTR, ZUPMTR, ZSTEQR, CSTEIN, ZPTEQR, ZHBTRD,
26 *> ZHEEV, CHEEVX, CHEEVD, ZHBEV, CHBEVX, CHBEVD,
27 *> ZHPEV, CHPEVX, CHPEVD, and ZSTEDC.
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 complex16_eig
56 *
57 * =====================================================================
58  SUBROUTINE zerrst( 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  DOUBLE PRECISION D( nmax ), E( nmax ), R( lw ), RW( lw ),
83  $ x( nmax )
84  COMPLEX*16 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 chkxer, zhbev, zhbevd, zhbevx, zhbtrd, zheev,
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 dble
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.d0 / dble( i+j )
121  10 CONTINUE
122  20 CONTINUE
123  DO 30 j = 1, nmax
124  d( j ) = dble( j )
125  e( j ) = 0.0d0
126  i1( j ) = j
127  i2( j ) = j
128  tau( j ) = 1.d0
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 * ZHETRD
138 *
139  srnamt = 'ZHETRD'
140  infot = 1
141  CALL zhetrd( '/', 0, a, 1, d, e, tau, w, 1, info )
142  CALL chkxer( 'ZHETRD', infot, nout, lerr, ok )
143  infot = 2
144  CALL zhetrd( 'U', -1, a, 1, d, e, tau, w, 1, info )
145  CALL chkxer( 'ZHETRD', infot, nout, lerr, ok )
146  infot = 4
147  CALL zhetrd( 'U', 2, a, 1, d, e, tau, w, 1, info )
148  CALL chkxer( 'ZHETRD', infot, nout, lerr, ok )
149  infot = 9
150  CALL zhetrd( 'U', 0, a, 1, d, e, tau, w, 0, info )
151  CALL chkxer( 'ZHETRD', infot, nout, lerr, ok )
152  nt = nt + 4
153 *
154 * ZUNGTR
155 *
156  srnamt = 'ZUNGTR'
157  infot = 1
158  CALL zungtr( '/', 0, a, 1, tau, w, 1, info )
159  CALL chkxer( 'ZUNGTR', infot, nout, lerr, ok )
160  infot = 2
161  CALL zungtr( 'U', -1, a, 1, tau, w, 1, info )
162  CALL chkxer( 'ZUNGTR', infot, nout, lerr, ok )
163  infot = 4
164  CALL zungtr( 'U', 2, a, 1, tau, w, 1, info )
165  CALL chkxer( 'ZUNGTR', infot, nout, lerr, ok )
166  infot = 7
167  CALL zungtr( 'U', 3, a, 3, tau, w, 1, info )
168  CALL chkxer( 'ZUNGTR', infot, nout, lerr, ok )
169  nt = nt + 4
170 *
171 * ZUNMTR
172 *
173  srnamt = 'ZUNMTR'
174  infot = 1
175  CALL zunmtr( '/', 'U', 'N', 0, 0, a, 1, tau, c, 1, w, 1, info )
176  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
177  infot = 2
178  CALL zunmtr( 'L', '/', 'N', 0, 0, a, 1, tau, c, 1, w, 1, info )
179  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
180  infot = 3
181  CALL zunmtr( 'L', 'U', '/', 0, 0, a, 1, tau, c, 1, w, 1, info )
182  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
183  infot = 4
184  CALL zunmtr( 'L', 'U', 'N', -1, 0, a, 1, tau, c, 1, w, 1,
185  $ info )
186  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
187  infot = 5
188  CALL zunmtr( 'L', 'U', 'N', 0, -1, a, 1, tau, c, 1, w, 1,
189  $ info )
190  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
191  infot = 7
192  CALL zunmtr( 'L', 'U', 'N', 2, 0, a, 1, tau, c, 2, w, 1, info )
193  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
194  infot = 7
195  CALL zunmtr( 'R', 'U', 'N', 0, 2, a, 1, tau, c, 1, w, 1, info )
196  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
197  infot = 10
198  CALL zunmtr( 'L', 'U', 'N', 2, 0, a, 2, tau, c, 1, w, 1, info )
199  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
200  infot = 12
201  CALL zunmtr( 'L', 'U', 'N', 0, 2, a, 1, tau, c, 1, w, 1, info )
202  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
203  infot = 12
204  CALL zunmtr( 'R', 'U', 'N', 2, 0, a, 1, tau, c, 2, w, 1, info )
205  CALL chkxer( 'ZUNMTR', infot, nout, lerr, ok )
206  nt = nt + 10
207 *
208 * ZHPTRD
209 *
210  srnamt = 'ZHPTRD'
211  infot = 1
212  CALL zhptrd( '/', 0, a, d, e, tau, info )
213  CALL chkxer( 'ZHPTRD', infot, nout, lerr, ok )
214  infot = 2
215  CALL zhptrd( 'U', -1, a, d, e, tau, info )
216  CALL chkxer( 'ZHPTRD', infot, nout, lerr, ok )
217  nt = nt + 2
218 *
219 * ZUPGTR
220 *
221  srnamt = 'ZUPGTR'
222  infot = 1
223  CALL zupgtr( '/', 0, a, tau, z, 1, w, info )
224  CALL chkxer( 'ZUPGTR', infot, nout, lerr, ok )
225  infot = 2
226  CALL zupgtr( 'U', -1, a, tau, z, 1, w, info )
227  CALL chkxer( 'ZUPGTR', infot, nout, lerr, ok )
228  infot = 6
229  CALL zupgtr( 'U', 2, a, tau, z, 1, w, info )
230  CALL chkxer( 'ZUPGTR', infot, nout, lerr, ok )
231  nt = nt + 3
232 *
233 * ZUPMTR
234 *
235  srnamt = 'ZUPMTR'
236  infot = 1
237  CALL zupmtr( '/', 'U', 'N', 0, 0, a, tau, c, 1, w, info )
238  CALL chkxer( 'ZUPMTR', infot, nout, lerr, ok )
239  infot = 2
240  CALL zupmtr( 'L', '/', 'N', 0, 0, a, tau, c, 1, w, info )
241  CALL chkxer( 'ZUPMTR', infot, nout, lerr, ok )
242  infot = 3
243  CALL zupmtr( 'L', 'U', '/', 0, 0, a, tau, c, 1, w, info )
244  CALL chkxer( 'ZUPMTR', infot, nout, lerr, ok )
245  infot = 4
246  CALL zupmtr( 'L', 'U', 'N', -1, 0, a, tau, c, 1, w, info )
247  CALL chkxer( 'ZUPMTR', infot, nout, lerr, ok )
248  infot = 5
249  CALL zupmtr( 'L', 'U', 'N', 0, -1, a, tau, c, 1, w, info )
250  CALL chkxer( 'ZUPMTR', infot, nout, lerr, ok )
251  infot = 9
252  CALL zupmtr( 'L', 'U', 'N', 2, 0, a, tau, c, 1, w, info )
253  CALL chkxer( 'ZUPMTR', infot, nout, lerr, ok )
254  nt = nt + 6
255 *
256 * ZPTEQR
257 *
258  srnamt = 'ZPTEQR'
259  infot = 1
260  CALL zpteqr( '/', 0, d, e, z, 1, rw, info )
261  CALL chkxer( 'ZPTEQR', infot, nout, lerr, ok )
262  infot = 2
263  CALL zpteqr( 'N', -1, d, e, z, 1, rw, info )
264  CALL chkxer( 'ZPTEQR', infot, nout, lerr, ok )
265  infot = 6
266  CALL zpteqr( 'V', 2, d, e, z, 1, rw, info )
267  CALL chkxer( 'ZPTEQR', infot, nout, lerr, ok )
268  nt = nt + 3
269 *
270 * ZSTEIN
271 *
272  srnamt = 'ZSTEIN'
273  infot = 1
274  CALL zstein( -1, d, e, 0, x, i1, i2, z, 1, rw, iw, i3, info )
275  CALL chkxer( 'ZSTEIN', infot, nout, lerr, ok )
276  infot = 4
277  CALL zstein( 0, d, e, -1, x, i1, i2, z, 1, rw, iw, i3, info )
278  CALL chkxer( 'ZSTEIN', infot, nout, lerr, ok )
279  infot = 4
280  CALL zstein( 0, d, e, 1, x, i1, i2, z, 1, rw, iw, i3, info )
281  CALL chkxer( 'ZSTEIN', infot, nout, lerr, ok )
282  infot = 9
283  CALL zstein( 2, d, e, 0, x, i1, i2, z, 1, rw, iw, i3, info )
284  CALL chkxer( 'ZSTEIN', infot, nout, lerr, ok )
285  nt = nt + 4
286 *
287 * ZSTEQR
288 *
289  srnamt = 'ZSTEQR'
290  infot = 1
291  CALL zsteqr( '/', 0, d, e, z, 1, rw, info )
292  CALL chkxer( 'ZSTEQR', infot, nout, lerr, ok )
293  infot = 2
294  CALL zsteqr( 'N', -1, d, e, z, 1, rw, info )
295  CALL chkxer( 'ZSTEQR', infot, nout, lerr, ok )
296  infot = 6
297  CALL zsteqr( 'V', 2, d, e, z, 1, rw, info )
298  CALL chkxer( 'ZSTEQR', infot, nout, lerr, ok )
299  nt = nt + 3
300 *
301 * ZSTEDC
302 *
303  srnamt = 'ZSTEDC'
304  infot = 1
305  CALL zstedc( '/', 0, d, e, z, 1, w, 1, rw, 1, iw, 1, info )
306  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
307  infot = 2
308  CALL zstedc( 'N', -1, d, e, z, 1, w, 1, rw, 1, iw, 1, info )
309  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
310  infot = 6
311  CALL zstedc( 'V', 2, d, e, z, 1, w, 4, rw, 23, iw, 28, info )
312  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
313  infot = 8
314  CALL zstedc( 'N', 2, d, e, z, 1, w, 0, rw, 1, iw, 1, info )
315  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
316  infot = 8
317  CALL zstedc( 'V', 2, d, e, z, 2, w, 0, rw, 23, iw, 28, info )
318  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
319  infot = 10
320  CALL zstedc( 'N', 2, d, e, z, 1, w, 1, rw, 0, iw, 1, info )
321  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
322  infot = 10
323  CALL zstedc( 'I', 2, d, e, z, 2, w, 1, rw, 1, iw, 12, info )
324  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
325  infot = 10
326  CALL zstedc( 'V', 2, d, e, z, 2, w, 4, rw, 1, iw, 28, info )
327  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
328  infot = 12
329  CALL zstedc( 'N', 2, d, e, z, 1, w, 1, rw, 1, iw, 0, info )
330  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
331  infot = 12
332  CALL zstedc( 'I', 2, d, e, z, 2, w, 1, rw, 23, iw, 0, info )
333  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
334  infot = 12
335  CALL zstedc( 'V', 2, d, e, z, 2, w, 4, rw, 23, iw, 0, info )
336  CALL chkxer( 'ZSTEDC', infot, nout, lerr, ok )
337  nt = nt + 11
338 *
339 * ZHEEVD
340 *
341  srnamt = 'ZHEEVD'
342  infot = 1
343  CALL zheevd( '/', 'U', 0, a, 1, x, w, 1, rw, 1, iw, 1, info )
344  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
345  infot = 2
346  CALL zheevd( 'N', '/', 0, a, 1, x, w, 1, rw, 1, iw, 1, info )
347  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
348  infot = 3
349  CALL zheevd( 'N', 'U', -1, a, 1, x, w, 1, rw, 1, iw, 1, info )
350  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
351  infot = 5
352  CALL zheevd( 'N', 'U', 2, a, 1, x, w, 3, rw, 2, iw, 1, info )
353  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
354  infot = 8
355  CALL zheevd( 'N', 'U', 1, a, 1, x, w, 0, rw, 1, iw, 1, info )
356  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
357  infot = 8
358  CALL zheevd( 'N', 'U', 2, a, 2, x, w, 2, rw, 2, iw, 1, info )
359  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
360  infot = 8
361  CALL zheevd( 'V', 'U', 2, a, 2, x, w, 3, rw, 25, iw, 12, info )
362  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
363  infot = 10
364  CALL zheevd( 'N', 'U', 1, a, 1, x, w, 1, rw, 0, iw, 1, info )
365  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
366  infot = 10
367  CALL zheevd( 'N', 'U', 2, a, 2, x, w, 3, rw, 1, iw, 1, info )
368  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
369  infot = 10
370  CALL zheevd( 'V', 'U', 2, a, 2, x, w, 8, rw, 18, iw, 12, info )
371  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
372  infot = 12
373  CALL zheevd( 'N', 'U', 1, a, 1, x, w, 1, rw, 1, iw, 0, info )
374  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
375  infot = 12
376  CALL zheevd( 'V', 'U', 2, a, 2, x, w, 8, rw, 25, iw, 11, info )
377  CALL chkxer( 'ZHEEVD', infot, nout, lerr, ok )
378  nt = nt + 12
379 *
380 * ZHEEV
381 *
382  srnamt = 'ZHEEV '
383  infot = 1
384  CALL zheev( '/', 'U', 0, a, 1, x, w, 1, rw, info )
385  CALL chkxer( 'ZHEEV ', infot, nout, lerr, ok )
386  infot = 2
387  CALL zheev( 'N', '/', 0, a, 1, x, w, 1, rw, info )
388  CALL chkxer( 'ZHEEV ', infot, nout, lerr, ok )
389  infot = 3
390  CALL zheev( 'N', 'U', -1, a, 1, x, w, 1, rw, info )
391  CALL chkxer( 'ZHEEV ', infot, nout, lerr, ok )
392  infot = 5
393  CALL zheev( 'N', 'U', 2, a, 1, x, w, 3, rw, info )
394  CALL chkxer( 'ZHEEV ', infot, nout, lerr, ok )
395  infot = 8
396  CALL zheev( 'N', 'U', 2, a, 2, x, w, 2, rw, info )
397  CALL chkxer( 'ZHEEV ', infot, nout, lerr, ok )
398  nt = nt + 5
399 *
400 * ZHEEVX
401 *
402  srnamt = 'ZHEEVX'
403  infot = 1
404  CALL zheevx( '/', 'A', 'U', 0, a, 1, 0.0d0, 0.0d0, 0, 0, 0.0d0,
405  $ m, x, z, 1, w, 1, rw, iw, i3, info )
406  CALL chkxer( 'ZHEEVX', infot, nout, lerr, ok )
407  infot = 2
408  CALL zheevx( 'V', '/', 'U', 0, a, 1, 0.0d0, 1.0d0, 1, 0, 0.0d0,
409  $ m, x, z, 1, w, 1, rw, iw, i3, info )
410  CALL chkxer( 'ZHEEVX', infot, nout, lerr, ok )
411  infot = 3
412  CALL zheevx( 'V', 'A', '/', 0, a, 1, 0.0d0, 0.0d0, 0, 0, 0.0d0,
413  $ m, x, z, 1, w, 1, rw, iw, i3, info )
414  infot = 4
415  CALL zheevx( 'V', 'A', 'U', -1, a, 1, 0.0d0, 0.0d0, 0, 0,
416  $ 0.0d0, m, x, z, 1, w, 1, rw, iw, i3, info )
417  CALL chkxer( 'ZHEEVX', infot, nout, lerr, ok )
418  infot = 6
419  CALL zheevx( 'V', 'A', 'U', 2, a, 1, 0.0d0, 0.0d0, 0, 0, 0.0d0,
420  $ m, x, z, 2, w, 3, rw, iw, i3, info )
421  CALL chkxer( 'ZHEEVX', infot, nout, lerr, ok )
422  infot = 8
423  CALL zheevx( 'V', 'V', 'U', 1, a, 1, 0.0d0, 0.0d0, 0, 0, 0.0d0,
424  $ m, x, z, 1, w, 1, rw, iw, i3, info )
425  CALL chkxer( 'ZHEEVX', infot, nout, lerr, ok )
426  infot = 9
427  CALL zheevx( 'V', 'I', 'U', 1, a, 1, 0.0d0, 0.0d0, 0, 0, 0.0d0,
428  $ m, x, z, 1, w, 1, rw, iw, i3, info )
429  CALL chkxer( 'ZHEEVX', infot, nout, lerr, ok )
430  infot = 10
431  CALL zheevx( 'V', 'I', 'U', 2, a, 2, 0.0d0, 0.0d0, 2, 1, 0.0d0,
432  $ m, x, z, 2, w, 3, rw, iw, i3, info )
433  CALL chkxer( 'ZHEEVX', infot, nout, lerr, ok )
434  infot = 15
435  CALL zheevx( 'V', 'A', 'U', 2, a, 2, 0.0d0, 0.0d0, 0, 0, 0.0d0,
436  $ m, x, z, 1, w, 3, rw, iw, i3, info )
437  CALL chkxer( 'ZHEEVX', infot, nout, lerr, ok )
438  infot = 17
439  CALL zheevx( 'V', 'A', 'U', 2, a, 2, 0.0d0, 0.0d0, 0, 0, 0.0d0,
440  $ m, x, z, 2, w, 2, rw, iw, i1, info )
441  CALL chkxer( 'ZHEEVX', infot, nout, lerr, ok )
442  nt = nt + 10
443 *
444 * ZHEEVR
445 *
446  srnamt = 'ZHEEVR'
447  n = 1
448  infot = 1
449  CALL zheevr( '/', 'A', 'U', 0, a, 1, 0.0d0, 0.0d0, 1, 1, 0.0d0,
450  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
451  $ 10*n, info )
452  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
453  infot = 2
454  CALL zheevr( 'V', '/', 'U', 0, a, 1, 0.0d0, 0.0d0, 1, 1, 0.0d0,
455  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
456  $ 10*n, info )
457  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
458  infot = 3
459  CALL zheevr( 'V', 'A', '/', -1, a, 1, 0.0d0, 0.0d0, 1, 1,
460  $ 0.0d0, m, r, z, 1, iw, q, 2*n, rw, 24*n,
461  $ iw( 2*n+1 ), 10*n, info )
462  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
463  infot = 4
464  CALL zheevr( 'V', 'A', 'U', -1, a, 1, 0.0d0, 0.0d0, 1, 1,
465  $ 0.0d0, m, r, z, 1, iw, q, 2*n, rw, 24*n,
466  $ iw( 2*n+1 ), 10*n, info )
467  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
468  infot = 6
469  CALL zheevr( 'V', 'A', 'U', 2, a, 1, 0.0d0, 0.0d0, 1, 1, 0.0d0,
470  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
471  $ 10*n, info )
472  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
473  infot = 8
474  CALL zheevr( 'V', 'V', 'U', 1, a, 1, 0.0d0, 0.0d0, 1, 1, 0.0d0,
475  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
476  $ 10*n, info )
477  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
478  infot = 9
479  CALL zheevr( 'V', 'I', 'U', 1, a, 1, 0.0d0, 0.0d0, 0, 1, 0.0d0,
480  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
481  $ 10*n, info )
482  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
483  infot = 10
484 *
485  CALL zheevr( 'V', 'I', 'U', 2, a, 2, 0.0d0, 0.0d0, 2, 1, 0.0d0,
486  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
487  $ 10*n, info )
488  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
489  infot = 15
490  CALL zheevr( 'V', 'I', 'U', 1, a, 1, 0.0d0, 0.0d0, 1, 1, 0.0d0,
491  $ m, r, z, 0, iw, q, 2*n, rw, 24*n, iw( 2*n+1 ),
492  $ 10*n, info )
493  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
494  infot = 18
495  CALL zheevr( 'V', 'I', 'U', 1, a, 1, 0.0d0, 0.0d0, 1, 1, 0.0d0,
496  $ m, r, z, 1, iw, q, 2*n-1, rw, 24*n, iw( 2*n+1 ),
497  $ 10*n, info )
498  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
499  infot = 20
500  CALL zheevr( 'V', 'I', 'U', 1, a, 1, 0.0d0, 0.0d0, 1, 1, 0.0d0,
501  $ m, r, z, 1, iw, q, 2*n, rw, 24*n-1, iw( 2*n-1 ),
502  $ 10*n, info )
503  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
504  infot = 22
505  CALL zheevr( 'V', 'I', 'U', 1, a, 1, 0.0d0, 0.0d0, 1, 1, 0.0d0,
506  $ m, r, z, 1, iw, q, 2*n, rw, 24*n, iw, 10*n-1,
507  $ info )
508  CALL chkxer( 'ZHEEVR', infot, nout, lerr, ok )
509  nt = nt + 12
510 *
511 * ZHPEVD
512 *
513  srnamt = 'ZHPEVD'
514  infot = 1
515  CALL zhpevd( '/', 'U', 0, a, x, z, 1, w, 1, rw, 1, iw, 1,
516  $ info )
517  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
518  infot = 2
519  CALL zhpevd( 'N', '/', 0, a, x, z, 1, w, 1, rw, 1, iw, 1,
520  $ info )
521  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
522  infot = 3
523  CALL zhpevd( 'N', 'U', -1, a, x, z, 1, w, 1, rw, 1, iw, 1,
524  $ info )
525  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
526  infot = 7
527  CALL zhpevd( 'V', 'U', 2, a, x, z, 1, w, 4, rw, 25, iw, 12,
528  $ info )
529  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
530  infot = 9
531  CALL zhpevd( 'N', 'U', 1, a, x, z, 1, w, 0, rw, 1, iw, 1,
532  $ info )
533  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
534  infot = 9
535  CALL zhpevd( 'N', 'U', 2, a, x, z, 2, w, 1, rw, 2, iw, 1,
536  $ info )
537  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
538  infot = 9
539  CALL zhpevd( 'V', 'U', 2, a, x, z, 2, w, 2, rw, 25, iw, 12,
540  $ info )
541  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
542  infot = 11
543  CALL zhpevd( 'N', 'U', 1, a, x, z, 1, w, 1, rw, 0, iw, 1,
544  $ info )
545  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
546  infot = 11
547  CALL zhpevd( 'N', 'U', 2, a, x, z, 2, w, 2, rw, 1, iw, 1,
548  $ info )
549  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
550  infot = 11
551  CALL zhpevd( 'V', 'U', 2, a, x, z, 2, w, 4, rw, 18, iw, 12,
552  $ info )
553  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
554  infot = 13
555  CALL zhpevd( 'N', 'U', 1, a, x, z, 1, w, 1, rw, 1, iw, 0,
556  $ info )
557  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
558  infot = 13
559  CALL zhpevd( 'N', 'U', 2, a, x, z, 2, w, 2, rw, 2, iw, 0,
560  $ info )
561  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
562  infot = 13
563  CALL zhpevd( 'V', 'U', 2, a, x, z, 2, w, 4, rw, 25, iw, 2,
564  $ info )
565  CALL chkxer( 'ZHPEVD', infot, nout, lerr, ok )
566  nt = nt + 13
567 *
568 * ZHPEV
569 *
570  srnamt = 'ZHPEV '
571  infot = 1
572  CALL zhpev( '/', 'U', 0, a, x, z, 1, w, rw, info )
573  CALL chkxer( 'ZHPEV ', infot, nout, lerr, ok )
574  infot = 2
575  CALL zhpev( 'N', '/', 0, a, x, z, 1, w, rw, info )
576  CALL chkxer( 'ZHPEV ', infot, nout, lerr, ok )
577  infot = 3
578  CALL zhpev( 'N', 'U', -1, a, x, z, 1, w, rw, info )
579  CALL chkxer( 'ZHPEV ', infot, nout, lerr, ok )
580  infot = 7
581  CALL zhpev( 'V', 'U', 2, a, x, z, 1, w, rw, info )
582  CALL chkxer( 'ZHPEV ', infot, nout, lerr, ok )
583  nt = nt + 4
584 *
585 * ZHPEVX
586 *
587  srnamt = 'ZHPEVX'
588  infot = 1
589  CALL zhpevx( '/', 'A', 'U', 0, a, 0.0d0, 0.0d0, 0, 0, 0.0d0, m,
590  $ x, z, 1, w, rw, iw, i3, info )
591  CALL chkxer( 'ZHPEVX', infot, nout, lerr, ok )
592  infot = 2
593  CALL zhpevx( 'V', '/', 'U', 0, a, 0.0d0, 1.0d0, 1, 0, 0.0d0, m,
594  $ x, z, 1, w, rw, iw, i3, info )
595  CALL chkxer( 'ZHPEVX', infot, nout, lerr, ok )
596  infot = 3
597  CALL zhpevx( 'V', 'A', '/', 0, a, 0.0d0, 0.0d0, 0, 0, 0.0d0, m,
598  $ x, z, 1, w, rw, iw, i3, info )
599  CALL chkxer( 'ZHPEVX', infot, nout, lerr, ok )
600  infot = 4
601  CALL zhpevx( 'V', 'A', 'U', -1, a, 0.0d0, 0.0d0, 0, 0, 0.0d0,
602  $ m, x, z, 1, w, rw, iw, i3, info )
603  CALL chkxer( 'ZHPEVX', infot, nout, lerr, ok )
604  infot = 7
605  CALL zhpevx( 'V', 'V', 'U', 1, a, 0.0d0, 0.0d0, 0, 0, 0.0d0, m,
606  $ x, z, 1, w, rw, iw, i3, info )
607  CALL chkxer( 'ZHPEVX', infot, nout, lerr, ok )
608  infot = 8
609  CALL zhpevx( 'V', 'I', 'U', 1, a, 0.0d0, 0.0d0, 0, 0, 0.0d0, m,
610  $ x, z, 1, w, rw, iw, i3, info )
611  CALL chkxer( 'ZHPEVX', infot, nout, lerr, ok )
612  infot = 9
613  CALL zhpevx( 'V', 'I', 'U', 2, a, 0.0d0, 0.0d0, 2, 1, 0.0d0, m,
614  $ x, z, 2, w, rw, iw, i3, info )
615  CALL chkxer( 'ZHPEVX', infot, nout, lerr, ok )
616  infot = 14
617  CALL zhpevx( 'V', 'A', 'U', 2, a, 0.0d0, 0.0d0, 0, 0, 0.0d0, m,
618  $ x, z, 1, w, rw, iw, i3, info )
619  CALL chkxer( 'ZHPEVX', 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 * ZHBTRD
627 *
628  srnamt = 'ZHBTRD'
629  infot = 1
630  CALL zhbtrd( '/', 'U', 0, 0, a, 1, d, e, z, 1, w, info )
631  CALL chkxer( 'ZHBTRD', infot, nout, lerr, ok )
632  infot = 2
633  CALL zhbtrd( 'N', '/', 0, 0, a, 1, d, e, z, 1, w, info )
634  CALL chkxer( 'ZHBTRD', infot, nout, lerr, ok )
635  infot = 3
636  CALL zhbtrd( 'N', 'U', -1, 0, a, 1, d, e, z, 1, w, info )
637  CALL chkxer( 'ZHBTRD', infot, nout, lerr, ok )
638  infot = 4
639  CALL zhbtrd( 'N', 'U', 0, -1, a, 1, d, e, z, 1, w, info )
640  CALL chkxer( 'ZHBTRD', infot, nout, lerr, ok )
641  infot = 6
642  CALL zhbtrd( 'N', 'U', 1, 1, a, 1, d, e, z, 1, w, info )
643  CALL chkxer( 'ZHBTRD', infot, nout, lerr, ok )
644  infot = 10
645  CALL zhbtrd( 'V', 'U', 2, 0, a, 1, d, e, z, 1, w, info )
646  CALL chkxer( 'ZHBTRD', infot, nout, lerr, ok )
647  nt = nt + 6
648 *
649 * ZHBEVD
650 *
651  srnamt = 'ZHBEVD'
652  infot = 1
653  CALL zhbevd( '/', 'U', 0, 0, a, 1, x, z, 1, w, 1, rw, 1, iw, 1,
654  $ info )
655  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
656  infot = 2
657  CALL zhbevd( 'N', '/', 0, 0, a, 1, x, z, 1, w, 1, rw, 1, iw, 1,
658  $ info )
659  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
660  infot = 3
661  CALL zhbevd( 'N', 'U', -1, 0, a, 1, x, z, 1, w, 1, rw, 1, iw,
662  $ 1, info )
663  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
664  infot = 4
665  CALL zhbevd( 'N', 'U', 0, -1, a, 1, x, z, 1, w, 1, rw, 1, iw,
666  $ 1, info )
667  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
668  infot = 6
669  CALL zhbevd( 'N', 'U', 2, 1, a, 1, x, z, 1, w, 2, rw, 2, iw, 1,
670  $ info )
671  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
672  infot = 9
673  CALL zhbevd( 'V', 'U', 2, 1, a, 2, x, z, 1, w, 8, rw, 25, iw,
674  $ 12, info )
675  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
676  infot = 11
677  CALL zhbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 0, rw, 1, iw, 1,
678  $ info )
679  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
680  infot = 11
681  CALL zhbevd( 'N', 'U', 2, 1, a, 2, x, z, 2, w, 1, rw, 2, iw, 1,
682  $ info )
683  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
684  infot = 11
685  CALL zhbevd( 'V', 'U', 2, 1, a, 2, x, z, 2, w, 2, rw, 25, iw,
686  $ 12, info )
687  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
688  infot = 13
689  CALL zhbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 1, rw, 0, iw, 1,
690  $ info )
691  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
692  infot = 13
693  CALL zhbevd( 'N', 'U', 2, 1, a, 2, x, z, 2, w, 2, rw, 1, iw, 1,
694  $ info )
695  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
696  infot = 13
697  CALL zhbevd( 'V', 'U', 2, 1, a, 2, x, z, 2, w, 8, rw, 2, iw,
698  $ 12, info )
699  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
700  infot = 15
701  CALL zhbevd( 'N', 'U', 1, 0, a, 1, x, z, 1, w, 1, rw, 1, iw, 0,
702  $ info )
703  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
704  infot = 15
705  CALL zhbevd( 'N', 'U', 2, 1, a, 2, x, z, 2, w, 2, rw, 2, iw, 0,
706  $ info )
707  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
708  infot = 15
709  CALL zhbevd( 'V', 'U', 2, 1, a, 2, x, z, 2, w, 8, rw, 25, iw,
710  $ 2, info )
711  CALL chkxer( 'ZHBEVD', infot, nout, lerr, ok )
712  nt = nt + 15
713 *
714 * ZHBEV
715 *
716  srnamt = 'ZHBEV '
717  infot = 1
718  CALL zhbev( '/', 'U', 0, 0, a, 1, x, z, 1, w, rw, info )
719  CALL chkxer( 'ZHBEV ', infot, nout, lerr, ok )
720  infot = 2
721  CALL zhbev( 'N', '/', 0, 0, a, 1, x, z, 1, w, rw, info )
722  CALL chkxer( 'ZHBEV ', infot, nout, lerr, ok )
723  infot = 3
724  CALL zhbev( 'N', 'U', -1, 0, a, 1, x, z, 1, w, rw, info )
725  CALL chkxer( 'ZHBEV ', infot, nout, lerr, ok )
726  infot = 4
727  CALL zhbev( 'N', 'U', 0, -1, a, 1, x, z, 1, w, rw, info )
728  CALL chkxer( 'ZHBEV ', infot, nout, lerr, ok )
729  infot = 6
730  CALL zhbev( 'N', 'U', 2, 1, a, 1, x, z, 1, w, rw, info )
731  CALL chkxer( 'ZHBEV ', infot, nout, lerr, ok )
732  infot = 9
733  CALL zhbev( 'V', 'U', 2, 0, a, 1, x, z, 1, w, rw, info )
734  CALL chkxer( 'ZHBEV ', infot, nout, lerr, ok )
735  nt = nt + 6
736 *
737 * ZHBEVX
738 *
739  srnamt = 'ZHBEVX'
740  infot = 1
741  CALL zhbevx( '/', 'A', 'U', 0, 0, a, 1, q, 1, 0.0d0, 0.0d0, 0,
742  $ 0, 0.0d0, m, x, z, 1, w, rw, iw, i3, info )
743  CALL chkxer( 'ZHBEVX', infot, nout, lerr, ok )
744  infot = 2
745  CALL zhbevx( 'V', '/', 'U', 0, 0, a, 1, q, 1, 0.0d0, 1.0d0, 1,
746  $ 0, 0.0d0, m, x, z, 1, w, rw, iw, i3, info )
747  CALL chkxer( 'ZHBEVX', infot, nout, lerr, ok )
748  infot = 3
749  CALL zhbevx( 'V', 'A', '/', 0, 0, a, 1, q, 1, 0.0d0, 0.0d0, 0,
750  $ 0, 0.0d0, m, x, z, 1, w, rw, iw, i3, info )
751  infot = 4
752  CALL zhbevx( 'V', 'A', 'U', -1, 0, a, 1, q, 1, 0.0d0, 0.0d0, 0,
753  $ 0, 0.0d0, m, x, z, 1, w, rw, iw, i3, info )
754  CALL chkxer( 'ZHBEVX', infot, nout, lerr, ok )
755  infot = 5
756  CALL zhbevx( 'V', 'A', 'U', 0, -1, a, 1, q, 1, 0.0d0, 0.0d0, 0,
757  $ 0, 0.0d0, m, x, z, 1, w, rw, iw, i3, info )
758  CALL chkxer( 'ZHBEVX', infot, nout, lerr, ok )
759  infot = 7
760  CALL zhbevx( 'V', 'A', 'U', 2, 1, a, 1, q, 2, 0.0d0, 0.0d0, 0,
761  $ 0, 0.0d0, m, x, z, 2, w, rw, iw, i3, info )
762  CALL chkxer( 'ZHBEVX', infot, nout, lerr, ok )
763  infot = 9
764  CALL zhbevx( 'V', 'A', 'U', 2, 0, a, 1, q, 1, 0.0d0, 0.0d0, 0,
765  $ 0, 0.0d0, m, x, z, 2, w, rw, iw, i3, info )
766  CALL chkxer( 'ZHBEVX', infot, nout, lerr, ok )
767  infot = 11
768  CALL zhbevx( 'V', 'V', 'U', 1, 0, a, 1, q, 1, 0.0d0, 0.0d0, 0,
769  $ 0, 0.0d0, m, x, z, 1, w, rw, iw, i3, info )
770  CALL chkxer( 'ZHBEVX', infot, nout, lerr, ok )
771  infot = 12
772  CALL zhbevx( 'V', 'I', 'U', 1, 0, a, 1, q, 1, 0.0d0, 0.0d0, 0,
773  $ 0, 0.0d0, m, x, z, 1, w, rw, iw, i3, info )
774  CALL chkxer( 'ZHBEVX', infot, nout, lerr, ok )
775  infot = 13
776  CALL zhbevx( 'V', 'I', 'U', 1, 0, a, 1, q, 1, 0.0d0, 0.0d0, 1,
777  $ 2, 0.0d0, m, x, z, 1, w, rw, iw, i3, info )
778  CALL chkxer( 'ZHBEVX', infot, nout, lerr, ok )
779  infot = 18
780  CALL zhbevx( 'V', 'A', 'U', 2, 0, a, 1, q, 2, 0.0d0, 0.0d0, 0,
781  $ 0, 0.0d0, m, x, z, 1, w, rw, iw, i3, info )
782  CALL chkxer( 'ZHBEVX', 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 ZERRST
802 *
803  END
subroutine zhpevd(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)
ZHPEVD computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matric...
Definition: zhpevd.f:203
subroutine zpteqr(COMPZ, N, D, E, Z, LDZ, WORK, INFO)
ZPTEQR
Definition: zpteqr.f:147
subroutine zhbev(JOBZ, UPLO, N, KD, AB, LDAB, W, Z, LDZ, WORK, RWORK, INFO)
ZHBEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrice...
Definition: zhbev.f:154
subroutine zhbevd(JOBZ, UPLO, N, KD, AB, LDAB, W, Z, LDZ, WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)
ZHBEVD computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matric...
Definition: zhbevd.f:217
subroutine zhetrd(UPLO, N, A, LDA, D, E, TAU, WORK, LWORK, INFO)
ZHETRD
Definition: zhetrd.f:194
subroutine zheevd(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)
ZHEEVD computes the eigenvalues and, optionally, the left and/or right eigenvectors for HE matrices ...
Definition: zheevd.f:207
subroutine zhbevx(JOBZ, RANGE, UPLO, N, KD, AB, LDAB, Q, LDQ, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, WORK, RWORK, IWORK, IFAIL, INFO)
ZHBEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matric...
Definition: zhbevx.f:269
subroutine zsteqr(COMPZ, N, D, E, Z, LDZ, WORK, INFO)
ZSTEQR
Definition: zsteqr.f:134
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine zheevx(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, WORK, LWORK, RWORK, IWORK, IFAIL, INFO)
ZHEEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for HE matrices ...
Definition: zheevx.f:261
subroutine zungtr(UPLO, N, A, LDA, TAU, WORK, LWORK, INFO)
ZUNGTR
Definition: zungtr.f:125
subroutine zstein(N, D, E, M, W, IBLOCK, ISPLIT, Z, LDZ, WORK, IWORK, IFAIL, INFO)
ZSTEIN
Definition: zstein.f:184
subroutine zstedc(COMPZ, N, D, E, Z, LDZ, WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)
ZSTEDC
Definition: zstedc.f:215
subroutine zhptrd(UPLO, N, AP, D, E, TAU, INFO)
ZHPTRD
Definition: zhptrd.f:153
subroutine zhpevx(JOBZ, RANGE, UPLO, N, AP, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, WORK, RWORK, IWORK, IFAIL, INFO)
ZHPEVX computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matric...
Definition: zhpevx.f:242
subroutine zheevr(JOBZ, RANGE, UPLO, N, A, LDA, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, ISUPPZ, WORK, LWORK, RWORK, LRWORK, IWORK, LIWORK, INFO)
ZHEEVR computes the eigenvalues and, optionally, the left and/or right eigenvectors for HE matrices ...
Definition: zheevr.f:357
subroutine zerrst(PATH, NUNIT)
ZERRST
Definition: zerrst.f:59
subroutine zunmtr(SIDE, UPLO, TRANS, M, N, A, LDA, TAU, C, LDC, WORK, LWORK, INFO)
ZUNMTR
Definition: zunmtr.f:173
subroutine zupmtr(SIDE, UPLO, TRANS, M, N, AP, TAU, C, LDC, WORK, INFO)
ZUPMTR
Definition: zupmtr.f:152
subroutine zhpev(JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, RWORK, INFO)
ZHPEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrice...
Definition: zhpev.f:140
subroutine zhbtrd(VECT, UPLO, N, KD, AB, LDAB, D, E, Q, LDQ, WORK, INFO)
ZHBTRD
Definition: zhbtrd.f:165
subroutine zheev(JOBZ, UPLO, N, A, LDA, W, WORK, LWORK, RWORK, INFO)
ZHEEV computes the eigenvalues and, optionally, the left and/or right eigenvectors for HE matrices ...
Definition: zheev.f:142
subroutine zupgtr(UPLO, N, AP, TAU, Q, LDQ, WORK, INFO)
ZUPGTR
Definition: zupgtr.f:116