LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zerrvxx.f
Go to the documentation of this file.
1 *> \brief \b ZERRVXX
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 ZERRVX( 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 *> ZERRVX tests the error exits for the COMPLEX*16 driver routines
25 *> for solving linear systems of equations.
26 *> \endverbatim
27 *
28 * Arguments:
29 * ==========
30 *
31 *> \param[in] PATH
32 *> \verbatim
33 *> PATH is CHARACTER*3
34 *> The LAPACK path name for the routines to be tested.
35 *> \endverbatim
36 *>
37 *> \param[in] NUNIT
38 *> \verbatim
39 *> NUNIT is INTEGER
40 *> The unit number for output.
41 *> \endverbatim
42 *
43 * Authors:
44 * ========
45 *
46 *> \author Univ. of Tennessee
47 *> \author Univ. of California Berkeley
48 *> \author Univ. of Colorado Denver
49 *> \author NAG Ltd.
50 *
51 *> \date November 2011
52 *
53 *> \ingroup complex16_lin
54 *
55 * =====================================================================
56  SUBROUTINE zerrvx( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.4.0) --
59 * -- LAPACK is a software package provided by Univ. of Tennessee, --
60 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
61 * November 2011
62 *
63 * .. Scalar Arguments ..
64  CHARACTER*3 path
65  INTEGER nunit
66 * ..
67 *
68 * =====================================================================
69 *
70 * .. Parameters ..
71  INTEGER nmax
72  parameter( nmax = 4 )
73 * ..
74 * .. Local Scalars ..
75  CHARACTER eq
76  CHARACTER*2 c2
77  INTEGER i, info, j, n_err_bnds, nparams
78  DOUBLE PRECISION rcond, rpvgrw, berr
79 * ..
80 * .. Local Arrays ..
81  INTEGER ip( nmax )
82  DOUBLE PRECISION c( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
83  $ rf( nmax ), rw( nmax ), err_bnds_n( nmax, 3 ),
84  $ err_bnds_c( nmax, 3 ), params( 1 )
85  COMPLEX*16 a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
86  $ w( 2*nmax ), x( nmax )
87 * ..
88 * .. External Functions ..
89  LOGICAL lsamen
90  EXTERNAL lsamen
91 * ..
92 * .. External Subroutines ..
93  EXTERNAL chkxer, zgbsv, zgbsvx, zgesv, zgesvx, zgtsv,
98 * ..
99 * .. Scalars in Common ..
100  LOGICAL lerr, ok
101  CHARACTER*32 srnamt
102  INTEGER infot, nout
103 * ..
104 * .. Common blocks ..
105  common / infoc / infot, nout, ok, lerr
106  common / srnamc / srnamt
107 * ..
108 * .. Intrinsic Functions ..
109  INTRINSIC dble, dcmplx
110 * ..
111 * .. Executable Statements ..
112 *
113  nout = nunit
114  WRITE( nout, fmt = * )
115  c2 = path( 2: 3 )
116 *
117 * Set the variables to innocuous values.
118 *
119  DO 20 j = 1, nmax
120  DO 10 i = 1, nmax
121  a( i, j ) = dcmplx( 1.d0 / dble( i+j ),
122  $ -1.d0 / dble( i+j ) )
123  af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
124  $ -1.d0 / dble( i+j ) )
125  10 continue
126  b( j ) = 0.d0
127  r1( j ) = 0.d0
128  r2( j ) = 0.d0
129  w( j ) = 0.d0
130  x( j ) = 0.d0
131  c( j ) = 0.d0
132  r( j ) = 0.d0
133  ip( j ) = j
134  20 continue
135  eq = ' '
136  ok = .true.
137 *
138  IF( lsamen( 2, c2, 'GE' ) ) THEN
139 *
140 * ZGESV
141 *
142  srnamt = 'ZGESV '
143  infot = 1
144  CALL zgesv( -1, 0, a, 1, ip, b, 1, info )
145  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
146  infot = 2
147  CALL zgesv( 0, -1, a, 1, ip, b, 1, info )
148  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
149  infot = 4
150  CALL zgesv( 2, 1, a, 1, ip, b, 2, info )
151  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
152  infot = 7
153  CALL zgesv( 2, 1, a, 2, ip, b, 1, info )
154  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
155 *
156 * ZGESVX
157 *
158  srnamt = 'ZGESVX'
159  infot = 1
160  CALL zgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
161  $ x, 1, rcond, r1, r2, w, rw, info )
162  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
163  infot = 2
164  CALL zgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
165  $ x, 1, rcond, r1, r2, w, rw, info )
166  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
167  infot = 3
168  CALL zgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
169  $ x, 1, rcond, r1, r2, w, rw, info )
170  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
171  infot = 4
172  CALL zgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
173  $ x, 1, rcond, r1, r2, w, rw, info )
174  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
175  infot = 6
176  CALL zgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
177  $ x, 2, rcond, r1, r2, w, rw, info )
178  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
179  infot = 8
180  CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
181  $ x, 2, rcond, r1, r2, w, rw, info )
182  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
183  infot = 10
184  eq = '/'
185  CALL zgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
186  $ x, 1, rcond, r1, r2, w, rw, info )
187  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
188  infot = 11
189  eq = 'R'
190  CALL zgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
191  $ x, 1, rcond, r1, r2, w, rw, info )
192  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
193  infot = 12
194  eq = 'C'
195  CALL zgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
196  $ x, 1, rcond, r1, r2, w, rw, info )
197  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
198  infot = 14
199  CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
200  $ x, 2, rcond, r1, r2, w, rw, info )
201  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
202  infot = 16
203  CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
204  $ x, 1, rcond, r1, r2, w, rw, info )
205  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
206 *
207 * ZGESVXX
208 *
209  n_err_bnds = 3
210  nparams = 1
211  srnamt = 'ZGESVXX'
212  infot = 1
213  CALL zgesvxx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b,
214  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
215  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
216  $ info )
217  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
218  infot = 2
219  CALL zgesvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b,
220  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
221  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
222  $ info )
223  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
224  infot = 3
225  CALL zgesvxx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b,
226  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
227  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
228  $ info )
229  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
230  infot = 4
231  CALL zgesvxx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b,
232  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
233  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
234  $ info )
235  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
236  infot = 6
237  CALL zgesvxx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b,
238  $ 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
239  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
240  $ info )
241  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
242  infot = 8
243  CALL zgesvxx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b,
244  $ 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
245  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
246  $ info )
247  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
248  infot = 10
249  eq = '/'
250  CALL zgesvxx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b,
251  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
252  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
253  $ info )
254  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
255  infot = 11
256  eq = 'R'
257  CALL zgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b,
258  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
259  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
260  $ info )
261  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
262  infot = 12
263  eq = 'C'
264  CALL zgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b,
265  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
266  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
267  $ info )
268  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
269  infot = 14
270  CALL zgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b,
271  $ 1, x, 2, rcond, rpvgrw, berr, n_err_bnds,
272  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
273  $ info )
274  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
275  infot = 16
276  CALL zgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b,
277  $ 2, x, 1, rcond, rpvgrw, berr, n_err_bnds,
278  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
279  $ info )
280  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
281 *
282  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
283 *
284 * ZGBSV
285 *
286  srnamt = 'ZGBSV '
287  infot = 1
288  CALL zgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
289  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
290  infot = 2
291  CALL zgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
292  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
293  infot = 3
294  CALL zgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
295  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
296  infot = 4
297  CALL zgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
298  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
299  infot = 6
300  CALL zgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
301  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
302  infot = 9
303  CALL zgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
304  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
305 *
306 * ZGBSVX
307 *
308  srnamt = 'ZGBSVX'
309  infot = 1
310  CALL zgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
311  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
312  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
313  infot = 2
314  CALL zgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
315  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
316  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
317  infot = 3
318  CALL zgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
319  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
320  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
321  infot = 4
322  CALL zgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
323  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
324  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
325  infot = 5
326  CALL zgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
327  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
328  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
329  infot = 6
330  CALL zgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
331  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
332  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
333  infot = 8
334  CALL zgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
335  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
336  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
337  infot = 10
338  CALL zgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
339  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
340  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
341  infot = 12
342  eq = '/'
343  CALL zgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
344  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
345  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
346  infot = 13
347  eq = 'R'
348  CALL zgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
349  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
350  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
351  infot = 14
352  eq = 'C'
353  CALL zgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
354  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
355  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
356  infot = 16
357  CALL zgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
358  $ b, 1, x, 2, rcond, r1, r2, w, rw, info )
359  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
360  infot = 18
361  CALL zgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
362  $ b, 2, x, 1, rcond, r1, r2, w, rw, info )
363  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
364 *
365 * ZGBSVXX
366 *
367  n_err_bnds = 3
368  nparams = 1
369  srnamt = 'ZGBSVXX'
370  infot = 1
371  CALL zgbsvxx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
372  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
373  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
374  $ info )
375  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
376  infot = 2
377  CALL zgbsvxx( 'N', '/', 0, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
378  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
379  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
380  $ info )
381  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
382  infot = 3
383  CALL zgbsvxx( 'N', 'N', -1, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
384  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
385  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
386  $ info )
387  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
388  infot = 4
389  CALL zgbsvxx( 'N', 'N', 2, -1, 1, 0, a, 1, af, 1, ip, eq,
390  $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
391  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
392  $ info )
393  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
394  infot = 5
395  CALL zgbsvxx( 'N', 'N', 2, 1, -1, 0, a, 1, af, 1, ip, eq,
396  $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
397  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
398  $ info )
399  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
400  infot = 6
401  CALL zgbsvxx( 'N', 'N', 0, 1, 1, -1, a, 1, af, 1, ip, eq, r, c,
402  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
403  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
404  $ info )
405  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
406  infot = 8
407  CALL zgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 2, af, 2, ip, eq, r, c,
408  $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
409  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
410  $ info )
411  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
412  infot = 10
413  CALL zgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 3, ip, eq, r, c,
414  $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
415  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
416  $ info )
417  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
418  infot = 12
419  eq = '/'
420  CALL zgbsvxx( 'F', 'N', 0, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
421  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
422  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
423  $ info )
424  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
425  infot = 13
426  eq = 'R'
427  CALL zgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
428  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
429  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
430  $ info )
431  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
432  infot = 14
433  eq = 'C'
434  CALL zgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
435  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
436  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
437  $ info )
438  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
439  infot = 15
440  CALL zgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
441  $ b, 1, x, 2, rcond, rpvgrw, berr, n_err_bnds,
442  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
443  $ info )
444  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
445  infot = 16
446  CALL zgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
447  $ b, 2, x, 1, rcond, rpvgrw, berr, n_err_bnds,
448  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
449  $ info )
450  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
451 *
452  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
453 *
454 * ZGTSV
455 *
456  srnamt = 'ZGTSV '
457  infot = 1
458  CALL zgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
459  $ info )
460  CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
461  infot = 2
462  CALL zgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
463  $ info )
464  CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
465  infot = 7
466  CALL zgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
467  CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
468 *
469 * ZGTSVX
470 *
471  srnamt = 'ZGTSVX'
472  infot = 1
473  CALL zgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
474  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
475  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
476  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
477  infot = 2
478  CALL zgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
479  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
480  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
481  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
482  infot = 3
483  CALL zgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
484  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
485  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
486  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
487  infot = 4
488  CALL zgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
489  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
490  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
491  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
492  infot = 14
493  CALL zgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
494  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
495  $ ip, b, 1, x, 2, rcond, r1, r2, w, rw, info )
496  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
497  infot = 16
498  CALL zgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
499  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
500  $ ip, b, 2, x, 1, rcond, r1, r2, w, rw, info )
501  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
502 *
503  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
504 *
505 * ZPOSV
506 *
507  srnamt = 'ZPOSV '
508  infot = 1
509  CALL zposv( '/', 0, 0, a, 1, b, 1, info )
510  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
511  infot = 2
512  CALL zposv( 'U', -1, 0, a, 1, b, 1, info )
513  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
514  infot = 3
515  CALL zposv( 'U', 0, -1, a, 1, b, 1, info )
516  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
517  infot = 5
518  CALL zposv( 'U', 2, 0, a, 1, b, 2, info )
519  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
520  infot = 7
521  CALL zposv( 'U', 2, 0, a, 2, b, 1, info )
522  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
523 *
524 * ZPOSVX
525 *
526  srnamt = 'ZPOSVX'
527  infot = 1
528  CALL zposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
529  $ rcond, r1, r2, w, rw, info )
530  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
531  infot = 2
532  CALL zposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
533  $ rcond, r1, r2, w, rw, info )
534  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
535  infot = 3
536  CALL zposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
537  $ rcond, r1, r2, w, rw, info )
538  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
539  infot = 4
540  CALL zposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
541  $ rcond, r1, r2, w, rw, info )
542  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
543  infot = 6
544  CALL zposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
545  $ rcond, r1, r2, w, rw, info )
546  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
547  infot = 8
548  CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
549  $ rcond, r1, r2, w, rw, info )
550  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
551  infot = 9
552  eq = '/'
553  CALL zposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
554  $ rcond, r1, r2, w, rw, info )
555  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
556  infot = 10
557  eq = 'Y'
558  CALL zposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
559  $ rcond, r1, r2, w, rw, info )
560  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
561  infot = 12
562  CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
563  $ rcond, r1, r2, w, rw, info )
564  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
565  infot = 14
566  CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
567  $ rcond, r1, r2, w, rw, info )
568  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
569 *
570 * ZPOSVXX
571 *
572  n_err_bnds = 3
573  nparams = 1
574  srnamt = 'ZPOSVXX'
575  infot = 1
576  CALL zposvxx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
577  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
578  $ err_bnds_c, nparams, params, w, rw, info )
579  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
580  infot = 2
581  CALL zposvxx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
582  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
583  $ err_bnds_c, nparams, params, w, rw, info )
584  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
585  infot = 3
586  CALL zposvxx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
587  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
588  $ err_bnds_c, nparams, params, w, rw, info )
589  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
590  infot = 4
591  CALL zposvxx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
592  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
593  $ err_bnds_c, nparams, params, w, rw, info )
594  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
595  infot = 6
596  CALL zposvxx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
597  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
598  $ err_bnds_c, nparams, params, w, rw, info )
599  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
600  infot = 8
601  CALL zposvxx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
602  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
603  $ err_bnds_c, nparams, params, w, rw, info )
604  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
605  infot = 9
606  eq = '/'
607  CALL zposvxx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
608  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
609  $ err_bnds_c, nparams, params, w, rw, info )
610  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
611  infot = 10
612  eq = 'Y'
613  CALL zposvxx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
614  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
615  $ err_bnds_c, nparams, params, w, rw, info )
616  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
617  infot = 12
618  CALL zposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
619  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
620  $ err_bnds_c, nparams, params, w, rw, info )
621  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
622  infot = 14
623  CALL zposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
624  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
625  $ err_bnds_c, nparams, params, w, rw, info )
626  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
627 *
628  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
629 *
630 * ZPPSV
631 *
632  srnamt = 'ZPPSV '
633  infot = 1
634  CALL zppsv( '/', 0, 0, a, b, 1, info )
635  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
636  infot = 2
637  CALL zppsv( 'U', -1, 0, a, b, 1, info )
638  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
639  infot = 3
640  CALL zppsv( 'U', 0, -1, a, b, 1, info )
641  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
642  infot = 6
643  CALL zppsv( 'U', 2, 0, a, b, 1, info )
644  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
645 *
646 * ZPPSVX
647 *
648  srnamt = 'ZPPSVX'
649  infot = 1
650  CALL zppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
651  $ r1, r2, w, rw, info )
652  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
653  infot = 2
654  CALL zppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
655  $ r1, r2, w, rw, info )
656  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
657  infot = 3
658  CALL zppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
659  $ r1, r2, w, rw, info )
660  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
661  infot = 4
662  CALL zppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
663  $ r1, r2, w, rw, info )
664  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
665  infot = 7
666  eq = '/'
667  CALL zppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
668  $ r1, r2, w, rw, info )
669  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
670  infot = 8
671  eq = 'Y'
672  CALL zppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
673  $ r1, r2, w, rw, info )
674  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
675  infot = 10
676  CALL zppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
677  $ r1, r2, w, rw, info )
678  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
679  infot = 12
680  CALL zppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
681  $ r1, r2, w, rw, info )
682  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
683 *
684  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
685 *
686 * ZPBSV
687 *
688  srnamt = 'ZPBSV '
689  infot = 1
690  CALL zpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
691  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
692  infot = 2
693  CALL zpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
694  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
695  infot = 3
696  CALL zpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
697  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
698  infot = 4
699  CALL zpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
700  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
701  infot = 6
702  CALL zpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
703  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
704  infot = 8
705  CALL zpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
706  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
707 *
708 * ZPBSVX
709 *
710  srnamt = 'ZPBSVX'
711  infot = 1
712  CALL zpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
713  $ rcond, r1, r2, w, rw, info )
714  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
715  infot = 2
716  CALL zpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
717  $ rcond, r1, r2, w, rw, info )
718  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
719  infot = 3
720  CALL zpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
721  $ 1, rcond, r1, r2, w, rw, info )
722  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
723  infot = 4
724  CALL zpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
725  $ 1, rcond, r1, r2, w, rw, info )
726  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
727  infot = 5
728  CALL zpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
729  $ 1, rcond, r1, r2, w, rw, info )
730  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
731  infot = 7
732  CALL zpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
733  $ rcond, r1, r2, w, rw, info )
734  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
735  infot = 9
736  CALL zpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
737  $ rcond, r1, r2, w, rw, info )
738  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
739  infot = 10
740  eq = '/'
741  CALL zpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
742  $ rcond, r1, r2, w, rw, info )
743  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
744  infot = 11
745  eq = 'Y'
746  CALL zpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
747  $ rcond, r1, r2, w, rw, info )
748  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
749  infot = 13
750  CALL zpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
751  $ rcond, r1, r2, w, rw, info )
752  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
753  infot = 15
754  CALL zpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
755  $ rcond, r1, r2, w, rw, info )
756  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
757 *
758  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
759 *
760 * ZPTSV
761 *
762  srnamt = 'ZPTSV '
763  infot = 1
764  CALL zptsv( -1, 0, r, a( 1, 1 ), b, 1, info )
765  CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
766  infot = 2
767  CALL zptsv( 0, -1, r, a( 1, 1 ), b, 1, info )
768  CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
769  infot = 6
770  CALL zptsv( 2, 0, r, a( 1, 1 ), b, 1, info )
771  CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
772 *
773 * ZPTSVX
774 *
775  srnamt = 'ZPTSVX'
776  infot = 1
777  CALL zptsvx( '/', 0, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
778  $ 1, rcond, r1, r2, w, rw, info )
779  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
780  infot = 2
781  CALL zptsvx( 'N', -1, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
782  $ 1, rcond, r1, r2, w, rw, info )
783  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
784  infot = 3
785  CALL zptsvx( 'N', 0, -1, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
786  $ 1, rcond, r1, r2, w, rw, info )
787  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
788  infot = 9
789  CALL zptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
790  $ 2, rcond, r1, r2, w, rw, info )
791  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
792  infot = 11
793  CALL zptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 2, x,
794  $ 1, rcond, r1, r2, w, rw, info )
795  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
796 *
797  ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
798 *
799 * ZHESV
800 *
801  srnamt = 'ZHESV '
802  infot = 1
803  CALL zhesv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
804  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
805  infot = 2
806  CALL zhesv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
807  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
808  infot = 3
809  CALL zhesv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
810  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
811  infot = 5
812  CALL zhesv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
813  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
814  infot = 8
815  CALL zhesv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
816  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
817 *
818 * ZHESVX
819 *
820  srnamt = 'ZHESVX'
821  infot = 1
822  CALL zhesvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
823  $ rcond, r1, r2, w, 1, rw, info )
824  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
825  infot = 2
826  CALL zhesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
827  $ rcond, r1, r2, w, 1, rw, info )
828  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
829  infot = 3
830  CALL zhesvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
831  $ rcond, r1, r2, w, 1, rw, info )
832  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
833  infot = 4
834  CALL zhesvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
835  $ rcond, r1, r2, w, 1, rw, info )
836  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
837  infot = 6
838  CALL zhesvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
839  $ rcond, r1, r2, w, 4, rw, info )
840  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
841  infot = 8
842  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
843  $ rcond, r1, r2, w, 4, rw, info )
844  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
845  infot = 11
846  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
847  $ rcond, r1, r2, w, 4, rw, info )
848  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
849  infot = 13
850  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
851  $ rcond, r1, r2, w, 4, rw, info )
852  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
853  infot = 18
854  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
855  $ rcond, r1, r2, w, 3, rw, info )
856  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
857 *
858 * ZHESVXX
859 *
860  n_err_bnds = 3
861  nparams = 1
862  srnamt = 'ZHESVXX'
863  infot = 1
864  CALL zhesvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
865  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
866  $ err_bnds_c, nparams, params, w, rw, info )
867  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
868  infot = 2
869  CALL zhesvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
870  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
871  $ err_bnds_c, nparams, params, w, rw, info )
872  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
873  infot = 3
874  CALL zhesvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
875  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
876  $ err_bnds_c, nparams, params, w, rw, info )
877  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
878  infot = 4
879  CALL zhesvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, c, b, 1, x,
880  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
881  $ err_bnds_c, nparams, params, w, rw, info )
882  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
883  infot = 6
884  CALL zhesvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, c, b, 2, x,
885  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
886  $ err_bnds_c, nparams, params, w, rw, info )
887  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
888  infot = 8
889  CALL zhesvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, c, b, 2, x,
890  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
891  $ err_bnds_c, nparams, params, w, rw, info )
892  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
893  infot = 9
894  eq = '/'
895  CALL zhesvxx( 'F', 'U', 0, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
896  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
897  $ err_bnds_c, nparams, params, w, rw, info )
898  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
899  infot = 10
900  eq = 'Y'
901  CALL zhesvxx( 'F', 'U', 1, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
902  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
903  $ err_bnds_c, nparams, params, w, rw, info )
904  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
905  infot = 12
906  CALL zhesvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, c, b, 1, x,
907  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
908  $ err_bnds_c, nparams, params, w, rw, info )
909  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
910  infot = 14
911  CALL zhesvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, c, b, 2, x,
912  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
913  $ err_bnds_c, nparams, params, w, rw, info )
914  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
915 *
916  ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
917 *
918 * ZHPSV
919 *
920  srnamt = 'ZHPSV '
921  infot = 1
922  CALL zhpsv( '/', 0, 0, a, ip, b, 1, info )
923  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
924  infot = 2
925  CALL zhpsv( 'U', -1, 0, a, ip, b, 1, info )
926  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
927  infot = 3
928  CALL zhpsv( 'U', 0, -1, a, ip, b, 1, info )
929  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
930  infot = 7
931  CALL zhpsv( 'U', 2, 0, a, ip, b, 1, info )
932  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
933 *
934 * ZHPSVX
935 *
936  srnamt = 'ZHPSVX'
937  infot = 1
938  CALL zhpsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
939  $ r2, w, rw, info )
940  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
941  infot = 2
942  CALL zhpsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
943  $ r2, w, rw, info )
944  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
945  infot = 3
946  CALL zhpsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
947  $ r2, w, rw, info )
948  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
949  infot = 4
950  CALL zhpsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
951  $ r2, w, rw, info )
952  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
953  infot = 9
954  CALL zhpsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
955  $ r2, w, rw, info )
956  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
957  infot = 11
958  CALL zhpsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
959  $ r2, w, rw, info )
960  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
961 *
962  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
963 *
964 * ZSYSV
965 *
966  srnamt = 'ZSYSV '
967  infot = 1
968  CALL zsysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
969  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
970  infot = 2
971  CALL zsysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
972  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
973  infot = 3
974  CALL zsysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
975  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
976  infot = 8
977  CALL zsysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
978  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
979 *
980 * ZSYSVX
981 *
982  srnamt = 'ZSYSVX'
983  infot = 1
984  CALL zsysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
985  $ rcond, r1, r2, w, 1, rw, info )
986  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
987  infot = 2
988  CALL zsysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
989  $ rcond, r1, r2, w, 1, rw, info )
990  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
991  infot = 3
992  CALL zsysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
993  $ rcond, r1, r2, w, 1, rw, info )
994  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
995  infot = 4
996  CALL zsysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
997  $ rcond, r1, r2, w, 1, rw, info )
998  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
999  infot = 6
1000  CALL zsysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
1001  $ rcond, r1, r2, w, 4, rw, info )
1002  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1003  infot = 8
1004  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
1005  $ rcond, r1, r2, w, 4, rw, info )
1006  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1007  infot = 11
1008  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
1009  $ rcond, r1, r2, w, 4, rw, info )
1010  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1011  infot = 13
1012  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
1013  $ rcond, r1, r2, w, 4, rw, info )
1014  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1015  infot = 18
1016  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
1017  $ rcond, r1, r2, w, 3, rw, info )
1018  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1019 *
1020 * ZSYSVXX
1021 *
1022  n_err_bnds = 3
1023  nparams = 1
1024  srnamt = 'ZSYSVXX'
1025  infot = 1
1026  eq = 'N'
1027  CALL zsysvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
1028  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1029  $ err_bnds_c, nparams, params, w, rw, info )
1030  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1031  infot = 2
1032  CALL zsysvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
1033  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1034  $ err_bnds_c, nparams, params, w, rw, info )
1035  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1036  infot = 3
1037  CALL zsysvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
1038  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1039  $ err_bnds_c, nparams, params, w, rw, info )
1040  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1041  infot = 4
1042  eq = '/'
1043  CALL zsysvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, r, b, 1, x,
1044  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1045  $ err_bnds_c, nparams, params, w, rw, info )
1046  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1047  eq = 'Y'
1048  infot = 6
1049  CALL zsysvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, r, b, 2, x,
1050  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1051  $ err_bnds_c, nparams, params, w, rw, info )
1052  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1053  infot = 8
1054  CALL zsysvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, r, b, 2, x,
1055  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1056  $ err_bnds_c, nparams, params, w, rw, info )
1057  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1058  infot = 12
1059  eq = 'N'
1060  CALL zsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 1, x,
1061  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1062  $ err_bnds_c, nparams, params, w, rw, info )
1063  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1064  infot = 14
1065  CALL zsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
1066  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1067  $ err_bnds_c, nparams, params, w, rw, info )
1068  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1069 *
1070  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
1071 *
1072 * ZSPSV
1073 *
1074  srnamt = 'ZSPSV '
1075  infot = 1
1076  CALL zspsv( '/', 0, 0, a, ip, b, 1, info )
1077  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1078  infot = 2
1079  CALL zspsv( 'U', -1, 0, a, ip, b, 1, info )
1080  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1081  infot = 3
1082  CALL zspsv( 'U', 0, -1, a, ip, b, 1, info )
1083  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1084  infot = 7
1085  CALL zspsv( 'U', 2, 0, a, ip, b, 1, info )
1086  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1087 *
1088 * ZSPSVX
1089 *
1090  srnamt = 'ZSPSVX'
1091  infot = 1
1092  CALL zspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1093  $ r2, w, rw, info )
1094  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1095  infot = 2
1096  CALL zspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1097  $ r2, w, rw, info )
1098  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1099  infot = 3
1100  CALL zspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1101  $ r2, w, rw, info )
1102  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1103  infot = 4
1104  CALL zspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1105  $ r2, w, rw, info )
1106  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1107  infot = 9
1108  CALL zspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1109  $ r2, w, rw, info )
1110  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1111  infot = 11
1112  CALL zspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1113  $ r2, w, rw, info )
1114  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1115  END IF
1116 *
1117 * Print a summary line.
1118 *
1119  IF( ok ) THEN
1120  WRITE( nout, fmt = 9999 )path
1121  ELSE
1122  WRITE( nout, fmt = 9998 )path
1123  END IF
1124 *
1125  9999 format( 1x, a3, ' drivers passed the tests of the error exits' )
1126  9998 format( ' *** ', a3, ' drivers failed the tests of the error ',
1127  $ 'exits ***' )
1128 *
1129  return
1130 *
1131 * End of ZERRVX
1132 *
1133  END