LAPACK  3.7.0
LAPACK: Linear Algebra PACKage
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 December 2016
52 *
53 *> \ingroup complex16_lin
54 *
55 * =====================================================================
56  SUBROUTINE zerrvx( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.7.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 * December 2016
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  REAL one
74  parameter ( one = 1.0d+0 )
75 * ..
76 * .. Local Scalars ..
77  CHARACTER eq
78  CHARACTER*2 c2
79  INTEGER i, info, j, n_err_bnds, nparams
80  DOUBLE PRECISION rcond, rpvgrw, berr
81 * ..
82 * .. Local Arrays ..
83  INTEGER ip( nmax )
84  DOUBLE PRECISION c( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
85  $ rf( nmax ), rw( nmax ), err_bnds_n( nmax, 3 ),
86  $ err_bnds_c( nmax, 3 ), params( 1 )
87  COMPLEX*16 a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
88  $ e( nmax ), w( 2*nmax ), x( nmax )
89 * ..
90 * .. External Functions ..
91  LOGICAL lsamen
92  EXTERNAL lsamen
93 * ..
94 * .. External Subroutines ..
95  EXTERNAL chkxer, zgbsv, zgbsvx, zgesv, zgesvx, zgtsv,
101 * ..
102 * .. Scalars in Common ..
103  LOGICAL lerr, ok
104  CHARACTER*32 srnamt
105  INTEGER infot, nout
106 * ..
107 * .. Common blocks ..
108  COMMON / infoc / infot, nout, ok, lerr
109  COMMON / srnamc / srnamt
110 * ..
111 * .. Intrinsic Functions ..
112  INTRINSIC dble, dcmplx
113 * ..
114 * .. Executable Statements ..
115 *
116  nout = nunit
117  WRITE( nout, fmt = * )
118  c2 = path( 2: 3 )
119 *
120 * Set the variables to innocuous values.
121 *
122  DO 20 j = 1, nmax
123  DO 10 i = 1, nmax
124  a( i, j ) = dcmplx( 1.d0 / dble( i+j ),
125  $ -1.d0 / dble( i+j ) )
126  af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
127  $ -1.d0 / dble( i+j ) )
128  10 CONTINUE
129  b( j ) = 0.d0
130  e( j ) = 0.d0
131  r1( j ) = 0.d0
132  r2( j ) = 0.d0
133  w( j ) = 0.d0
134  x( j ) = 0.d0
135  c( j ) = 0.d0
136  r( j ) = 0.d0
137  ip( j ) = j
138  20 CONTINUE
139  eq = ' '
140  ok = .true.
141 *
142  IF( lsamen( 2, c2, 'GE' ) ) THEN
143 *
144 * ZGESV
145 *
146  srnamt = 'ZGESV '
147  infot = 1
148  CALL zgesv( -1, 0, a, 1, ip, b, 1, info )
149  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
150  infot = 2
151  CALL zgesv( 0, -1, a, 1, ip, b, 1, info )
152  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
153  infot = 4
154  CALL zgesv( 2, 1, a, 1, ip, b, 2, info )
155  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
156  infot = 7
157  CALL zgesv( 2, 1, a, 2, ip, b, 1, info )
158  CALL chkxer( 'ZGESV ', infot, nout, lerr, ok )
159 *
160 * ZGESVX
161 *
162  srnamt = 'ZGESVX'
163  infot = 1
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 = 2
168  CALL zgesvx( 'N', '/', 0, 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 = 3
172  CALL zgesvx( 'N', 'N', -1, 0, 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 = 4
176  CALL zgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
177  $ x, 1, rcond, r1, r2, w, rw, info )
178  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
179  infot = 6
180  CALL zgesvx( 'N', 'N', 2, 1, a, 1, af, 2, 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 = 8
184  CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
185  $ x, 2, rcond, r1, r2, w, rw, info )
186  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
187  infot = 10
188  eq = '/'
189  CALL zgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
190  $ x, 1, rcond, r1, r2, w, rw, info )
191  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
192  infot = 11
193  eq = 'R'
194  CALL zgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
195  $ x, 1, rcond, r1, r2, w, rw, info )
196  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
197  infot = 12
198  eq = 'C'
199  CALL zgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
200  $ x, 1, rcond, r1, r2, w, rw, info )
201  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
202  infot = 14
203  CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
204  $ x, 2, rcond, r1, r2, w, rw, info )
205  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
206  infot = 16
207  CALL zgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
208  $ x, 1, rcond, r1, r2, w, rw, info )
209  CALL chkxer( 'ZGESVX', infot, nout, lerr, ok )
210 *
211 * ZGESVXX
212 *
213  n_err_bnds = 3
214  nparams = 1
215  srnamt = 'ZGESVXX'
216  infot = 1
217  CALL zgesvxx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b,
218  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
219  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
220  $ info )
221  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
222  infot = 2
223  CALL zgesvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b,
224  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
225  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
226  $ info )
227  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
228  infot = 3
229  CALL zgesvxx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b,
230  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
231  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
232  $ info )
233  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
234  infot = 4
235  CALL zgesvxx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b,
236  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
237  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
238  $ info )
239  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
240  infot = 6
241  CALL zgesvxx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b,
242  $ 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
243  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
244  $ info )
245  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
246  infot = 8
247  CALL zgesvxx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b,
248  $ 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
249  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
250  $ info )
251  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
252  infot = 10
253  eq = '/'
254  CALL zgesvxx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b,
255  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
256  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
257  $ info )
258  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
259  infot = 11
260  eq = 'R'
261  CALL zgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b,
262  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
263  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
264  $ info )
265  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
266  infot = 12
267  eq = 'C'
268  CALL zgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b,
269  $ 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
270  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
271  $ info )
272  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
273  infot = 14
274  CALL zgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b,
275  $ 1, x, 2, rcond, rpvgrw, berr, n_err_bnds,
276  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
277  $ info )
278  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
279  infot = 16
280  CALL zgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b,
281  $ 2, x, 1, rcond, rpvgrw, berr, n_err_bnds,
282  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
283  $ info )
284  CALL chkxer( 'ZGESVXX', infot, nout, lerr, ok )
285 *
286  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
287 *
288 * ZGBSV
289 *
290  srnamt = 'ZGBSV '
291  infot = 1
292  CALL zgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
293  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
294  infot = 2
295  CALL zgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
296  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
297  infot = 3
298  CALL zgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
299  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
300  infot = 4
301  CALL zgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
302  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
303  infot = 6
304  CALL zgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
305  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
306  infot = 9
307  CALL zgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
308  CALL chkxer( 'ZGBSV ', infot, nout, lerr, ok )
309 *
310 * ZGBSVX
311 *
312  srnamt = 'ZGBSVX'
313  infot = 1
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 = 2
318  CALL zgbsvx( 'N', '/', 0, 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 = 3
322  CALL zgbsvx( 'N', 'N', -1, 0, 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 = 4
326  CALL zgbsvx( 'N', 'N', 1, -1, 0, 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 = 5
330  CALL zgbsvx( 'N', 'N', 1, 0, -1, 0, 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 = 6
334  CALL zgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, 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 = 8
338  CALL zgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, 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 = 10
342  CALL zgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
343  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
344  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
345  infot = 12
346  eq = '/'
347  CALL zgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
348  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
349  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
350  infot = 13
351  eq = 'R'
352  CALL zgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
353  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
354  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
355  infot = 14
356  eq = 'C'
357  CALL zgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
358  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
359  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
360  infot = 16
361  CALL zgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
362  $ b, 1, x, 2, rcond, r1, r2, w, rw, info )
363  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
364  infot = 18
365  CALL zgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
366  $ b, 2, x, 1, rcond, r1, r2, w, rw, info )
367  CALL chkxer( 'ZGBSVX', infot, nout, lerr, ok )
368 *
369 * ZGBSVXX
370 *
371  n_err_bnds = 3
372  nparams = 1
373  srnamt = 'ZGBSVXX'
374  infot = 1
375  CALL zgbsvxx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
376  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
377  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
378  $ info )
379  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
380  infot = 2
381  CALL zgbsvxx( 'N', '/', 0, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
382  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
383  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
384  $ info )
385  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
386  infot = 3
387  CALL zgbsvxx( 'N', 'N', -1, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
388  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
389  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
390  $ info )
391  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
392  infot = 4
393  CALL zgbsvxx( 'N', 'N', 2, -1, 1, 0, a, 1, af, 1, ip, eq,
394  $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
395  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
396  $ info )
397  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
398  infot = 5
399  CALL zgbsvxx( 'N', 'N', 2, 1, -1, 0, a, 1, af, 1, ip, eq,
400  $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
401  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
402  $ info )
403  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
404  infot = 6
405  CALL zgbsvxx( 'N', 'N', 0, 1, 1, -1, a, 1, af, 1, ip, eq, r, c,
406  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
407  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
408  $ info )
409  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
410  infot = 8
411  CALL zgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 2, af, 2, ip, eq, r, c,
412  $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
413  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
414  $ info )
415  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
416  infot = 10
417  CALL zgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 3, ip, eq, r, c,
418  $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
419  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
420  $ info )
421  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
422  infot = 12
423  eq = '/'
424  CALL zgbsvxx( 'F', 'N', 0, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
425  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
426  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
427  $ info )
428  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
429  infot = 13
430  eq = 'R'
431  CALL zgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
432  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
433  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
434  $ info )
435  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
436  infot = 14
437  eq = 'C'
438  CALL zgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
439  $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
440  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
441  $ info )
442  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
443  infot = 15
444  CALL zgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
445  $ b, 1, x, 2, rcond, rpvgrw, berr, n_err_bnds,
446  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
447  $ info )
448  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
449  infot = 16
450  CALL zgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
451  $ b, 2, x, 1, rcond, rpvgrw, berr, n_err_bnds,
452  $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
453  $ info )
454  CALL chkxer( 'ZGBSVXX', infot, nout, lerr, ok )
455 *
456  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
457 *
458 * ZGTSV
459 *
460  srnamt = 'ZGTSV '
461  infot = 1
462  CALL zgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
463  $ info )
464  CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
465  infot = 2
466  CALL zgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
467  $ info )
468  CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
469  infot = 7
470  CALL zgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
471  CALL chkxer( 'ZGTSV ', infot, nout, lerr, ok )
472 *
473 * ZGTSVX
474 *
475  srnamt = 'ZGTSVX'
476  infot = 1
477  CALL zgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
478  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
479  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
480  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
481  infot = 2
482  CALL zgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
483  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
484  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
485  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
486  infot = 3
487  CALL zgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
488  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
489  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
490  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
491  infot = 4
492  CALL zgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
493  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
494  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
495  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
496  infot = 14
497  CALL zgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
498  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
499  $ ip, b, 1, x, 2, rcond, r1, r2, w, rw, info )
500  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
501  infot = 16
502  CALL zgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
503  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
504  $ ip, b, 2, x, 1, rcond, r1, r2, w, rw, info )
505  CALL chkxer( 'ZGTSVX', infot, nout, lerr, ok )
506 *
507  ELSE IF( lsamen( 2, c2, 'HR' ) ) THEN
508 *
509 * ZHESV_ROOK
510 *
511  srnamt = 'ZHESV_ROOK'
512  infot = 1
513  CALL zhesv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
514  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
515  infot = 2
516  CALL zhesv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
517  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
518  infot = 3
519  CALL zhesv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
520  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
521  infot = 8
522  CALL zhesv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
523  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
524 *
525  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
526 *
527 * ZPOSV
528 *
529  srnamt = 'ZPOSV '
530  infot = 1
531  CALL zposv( '/', 0, 0, a, 1, b, 1, info )
532  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
533  infot = 2
534  CALL zposv( 'U', -1, 0, a, 1, b, 1, info )
535  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
536  infot = 3
537  CALL zposv( 'U', 0, -1, a, 1, b, 1, info )
538  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
539  infot = 5
540  CALL zposv( 'U', 2, 0, a, 1, b, 2, info )
541  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
542  infot = 7
543  CALL zposv( 'U', 2, 0, a, 2, b, 1, info )
544  CALL chkxer( 'ZPOSV ', infot, nout, lerr, ok )
545 *
546 * ZPOSVX
547 *
548  srnamt = 'ZPOSVX'
549  infot = 1
550  CALL zposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
551  $ rcond, r1, r2, w, rw, info )
552  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
553  infot = 2
554  CALL zposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
555  $ rcond, r1, r2, w, rw, info )
556  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
557  infot = 3
558  CALL zposvx( 'N', '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 = 4
562  CALL zposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
563  $ rcond, r1, r2, w, rw, info )
564  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
565  infot = 6
566  CALL zposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
567  $ rcond, r1, r2, w, rw, info )
568  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
569  infot = 8
570  CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
571  $ rcond, r1, r2, w, rw, info )
572  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
573  infot = 9
574  eq = '/'
575  CALL zposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
576  $ rcond, r1, r2, w, rw, info )
577  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
578  infot = 10
579  eq = 'Y'
580  CALL zposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
581  $ rcond, r1, r2, w, rw, info )
582  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
583  infot = 12
584  CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
585  $ rcond, r1, r2, w, rw, info )
586  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
587  infot = 14
588  CALL zposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
589  $ rcond, r1, r2, w, rw, info )
590  CALL chkxer( 'ZPOSVX', infot, nout, lerr, ok )
591 *
592 * ZPOSVXX
593 *
594  n_err_bnds = 3
595  nparams = 1
596  srnamt = 'ZPOSVXX'
597  infot = 1
598  CALL zposvxx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
599  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
600  $ err_bnds_c, nparams, params, w, rw, info )
601  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
602  infot = 2
603  CALL zposvxx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
604  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
605  $ err_bnds_c, nparams, params, w, rw, info )
606  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
607  infot = 3
608  CALL zposvxx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
609  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
610  $ err_bnds_c, nparams, params, w, rw, info )
611  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
612  infot = 4
613  CALL zposvxx( 'N', 'U', 0, -1, 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 = 6
618  CALL zposvxx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, 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 = 8
623  CALL zposvxx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
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  infot = 9
628  eq = '/'
629  CALL zposvxx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
630  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
631  $ err_bnds_c, nparams, params, w, rw, info )
632  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
633  infot = 10
634  eq = 'Y'
635  CALL zposvxx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
636  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
637  $ err_bnds_c, nparams, params, w, rw, info )
638  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
639  infot = 12
640  CALL zposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
641  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
642  $ err_bnds_c, nparams, params, w, rw, info )
643  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
644  infot = 14
645  CALL zposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
646  $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
647  $ err_bnds_c, nparams, params, w, rw, info )
648  CALL chkxer( 'ZPOSVXX', infot, nout, lerr, ok )
649 *
650  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
651 *
652 * ZPPSV
653 *
654  srnamt = 'ZPPSV '
655  infot = 1
656  CALL zppsv( '/', 0, 0, a, b, 1, info )
657  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
658  infot = 2
659  CALL zppsv( 'U', -1, 0, a, b, 1, info )
660  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
661  infot = 3
662  CALL zppsv( 'U', 0, -1, a, b, 1, info )
663  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
664  infot = 6
665  CALL zppsv( 'U', 2, 0, a, b, 1, info )
666  CALL chkxer( 'ZPPSV ', infot, nout, lerr, ok )
667 *
668 * ZPPSVX
669 *
670  srnamt = 'ZPPSVX'
671  infot = 1
672  CALL zppsvx( '/', 'U', 0, 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 = 2
676  CALL zppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
677  $ r1, r2, w, rw, info )
678  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
679  infot = 3
680  CALL zppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
681  $ r1, r2, w, rw, info )
682  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
683  infot = 4
684  CALL zppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
685  $ r1, r2, w, rw, info )
686  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
687  infot = 7
688  eq = '/'
689  CALL zppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
690  $ r1, r2, w, rw, info )
691  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
692  infot = 8
693  eq = 'Y'
694  CALL zppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
695  $ r1, r2, w, rw, info )
696  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
697  infot = 10
698  CALL zppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
699  $ r1, r2, w, rw, info )
700  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
701  infot = 12
702  CALL zppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
703  $ r1, r2, w, rw, info )
704  CALL chkxer( 'ZPPSVX', infot, nout, lerr, ok )
705 *
706  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
707 *
708 * ZPBSV
709 *
710  srnamt = 'ZPBSV '
711  infot = 1
712  CALL zpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
713  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
714  infot = 2
715  CALL zpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
716  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
717  infot = 3
718  CALL zpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
719  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
720  infot = 4
721  CALL zpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
722  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
723  infot = 6
724  CALL zpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
725  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
726  infot = 8
727  CALL zpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
728  CALL chkxer( 'ZPBSV ', infot, nout, lerr, ok )
729 *
730 * ZPBSVX
731 *
732  srnamt = 'ZPBSVX'
733  infot = 1
734  CALL zpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
735  $ rcond, r1, r2, w, rw, info )
736  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
737  infot = 2
738  CALL zpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
739  $ rcond, r1, r2, w, rw, info )
740  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
741  infot = 3
742  CALL zpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
743  $ 1, rcond, r1, r2, w, rw, info )
744  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
745  infot = 4
746  CALL zpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
747  $ 1, rcond, r1, r2, w, rw, info )
748  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
749  infot = 5
750  CALL zpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
751  $ 1, rcond, r1, r2, w, rw, info )
752  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
753  infot = 7
754  CALL zpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
755  $ rcond, r1, r2, w, rw, info )
756  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
757  infot = 9
758  CALL zpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
759  $ rcond, r1, r2, w, rw, info )
760  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
761  infot = 10
762  eq = '/'
763  CALL zpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
764  $ rcond, r1, r2, w, rw, info )
765  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
766  infot = 11
767  eq = 'Y'
768  CALL zpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
769  $ rcond, r1, r2, w, rw, info )
770  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
771  infot = 13
772  CALL zpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
773  $ rcond, r1, r2, w, rw, info )
774  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
775  infot = 15
776  CALL zpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
777  $ rcond, r1, r2, w, rw, info )
778  CALL chkxer( 'ZPBSVX', infot, nout, lerr, ok )
779 *
780  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
781 *
782 * ZPTSV
783 *
784  srnamt = 'ZPTSV '
785  infot = 1
786  CALL zptsv( -1, 0, r, a( 1, 1 ), b, 1, info )
787  CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
788  infot = 2
789  CALL zptsv( 0, -1, r, a( 1, 1 ), b, 1, info )
790  CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
791  infot = 6
792  CALL zptsv( 2, 0, r, a( 1, 1 ), b, 1, info )
793  CALL chkxer( 'ZPTSV ', infot, nout, lerr, ok )
794 *
795 * ZPTSVX
796 *
797  srnamt = 'ZPTSVX'
798  infot = 1
799  CALL zptsvx( '/', 0, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
800  $ 1, rcond, r1, r2, w, rw, info )
801  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
802  infot = 2
803  CALL zptsvx( 'N', -1, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
804  $ 1, rcond, r1, r2, w, rw, info )
805  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
806  infot = 3
807  CALL zptsvx( 'N', 0, -1, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
808  $ 1, rcond, r1, r2, w, rw, info )
809  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
810  infot = 9
811  CALL zptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
812  $ 2, rcond, r1, r2, w, rw, info )
813  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
814  infot = 11
815  CALL zptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 2, x,
816  $ 1, rcond, r1, r2, w, rw, info )
817  CALL chkxer( 'ZPTSVX', infot, nout, lerr, ok )
818 *
819  ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
820 *
821 * ZHESV
822 *
823  srnamt = 'ZHESV '
824  infot = 1
825  CALL zhesv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
826  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
827  infot = 2
828  CALL zhesv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
829  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
830  infot = 3
831  CALL zhesv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
832  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
833  infot = 5
834  CALL zhesv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
835  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
836  infot = 8
837  CALL zhesv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
838  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
839  infot = 10
840  CALL zhesv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
841  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
842  infot = 10
843  CALL zhesv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
844  CALL chkxer( 'ZHESV ', infot, nout, lerr, ok )
845 *
846 * ZHESVX
847 *
848  srnamt = 'ZHESVX'
849  infot = 1
850  CALL zhesvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
851  $ rcond, r1, r2, w, 1, rw, info )
852  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
853  infot = 2
854  CALL zhesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
855  $ rcond, r1, r2, w, 1, rw, info )
856  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
857  infot = 3
858  CALL zhesvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
859  $ rcond, r1, r2, w, 1, rw, info )
860  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
861  infot = 4
862  CALL zhesvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
863  $ rcond, r1, r2, w, 1, rw, info )
864  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
865  infot = 6
866  CALL zhesvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
867  $ rcond, r1, r2, w, 4, rw, info )
868  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
869  infot = 8
870  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
871  $ rcond, r1, r2, w, 4, rw, info )
872  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
873  infot = 11
874  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
875  $ rcond, r1, r2, w, 4, rw, info )
876  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
877  infot = 13
878  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
879  $ rcond, r1, r2, w, 4, rw, info )
880  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
881  infot = 18
882  CALL zhesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
883  $ rcond, r1, r2, w, 3, rw, info )
884  CALL chkxer( 'ZHESVX', infot, nout, lerr, ok )
885 *
886 * ZHESVXX
887 *
888  n_err_bnds = 3
889  nparams = 1
890  srnamt = 'ZHESVXX'
891  infot = 1
892  CALL zhesvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
893  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
894  $ err_bnds_c, nparams, params, w, rw, info )
895  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
896  infot = 2
897  CALL zhesvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
898  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
899  $ err_bnds_c, nparams, params, w, rw, info )
900  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
901  infot = 3
902  CALL zhesvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
903  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
904  $ err_bnds_c, nparams, params, w, rw, info )
905  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
906  infot = 4
907  CALL zhesvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, c, b, 1, x,
908  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
909  $ err_bnds_c, nparams, params, w, rw, info )
910  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
911  infot = 6
912  CALL zhesvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, c, b, 2, x,
913  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
914  $ err_bnds_c, nparams, params, w, rw, info )
915  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
916  infot = 8
917  CALL zhesvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, c, b, 2, x,
918  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
919  $ err_bnds_c, nparams, params, w, rw, info )
920  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
921  infot = 9
922  eq = '/'
923  CALL zhesvxx( 'F', 'U', 0, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
924  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
925  $ err_bnds_c, nparams, params, w, rw, info )
926  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
927  infot = 10
928  eq = 'Y'
929  CALL zhesvxx( 'F', 'U', 1, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
930  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
931  $ err_bnds_c, nparams, params, w, rw, info )
932  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
933  infot = 12
934  CALL zhesvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, c, b, 1, x,
935  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
936  $ err_bnds_c, nparams, params, w, rw, info )
937  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
938  infot = 14
939  CALL zhesvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, c, b, 2, x,
940  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
941  $ err_bnds_c, nparams, params, w, rw, info )
942  CALL chkxer( 'ZHESVXX', infot, nout, lerr, ok )
943 *
944  ELSE IF( lsamen( 2, c2, 'HR' ) ) THEN
945 *
946 * ZHESV_ROOK
947 *
948  srnamt = 'ZHESV_ROOK'
949  infot = 1
950  CALL zhesv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
951  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
952  infot = 2
953  CALL zhesv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
954  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
955  infot = 3
956  CALL zhesv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
957  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
958  infot = 8
959  CALL zhesv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
960  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
961  infot = 10
962  CALL zhesv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
963  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
964  infot = 10
965  CALL zhesv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
966  CALL chkxer( 'ZHESV_ROOK', infot, nout, lerr, ok )
967 *
968  ELSE IF( lsamen( 2, c2, 'HK' ) ) THEN
969 *
970 * ZSYSV_RK
971 *
972 * Test error exits of the driver that uses factorization
973 * of a Hermitian indefinite matrix with rook
974 * (bounded Bunch-Kaufman) pivoting with the new storage
975 * format for factors L ( or U) and D.
976 *
977 * L (or U) is stored in A, diagonal of D is stored on the
978 * diagonal of A, subdiagonal of D is stored in a separate array E.
979 *
980  srnamt = 'ZHESV_RK'
981  infot = 1
982  CALL zhesv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
983  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
984  infot = 2
985  CALL zhesv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
986  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
987  infot = 3
988  CALL zhesv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
989  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
990  infot = 5
991  CALL zhesv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
992  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
993  infot = 9
994  CALL zhesv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
995  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
996  infot = 11
997  CALL zhesv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
998  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
999  infot = 11
1000  CALL zhesv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
1001  CALL chkxer( 'ZHESV_RK', infot, nout, lerr, ok )
1002 *
1003  ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
1004 *
1005 * ZHPSV
1006 *
1007  srnamt = 'ZHPSV '
1008  infot = 1
1009  CALL zhpsv( '/', 0, 0, a, ip, b, 1, info )
1010  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
1011  infot = 2
1012  CALL zhpsv( 'U', -1, 0, a, ip, b, 1, info )
1013  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
1014  infot = 3
1015  CALL zhpsv( 'U', 0, -1, a, ip, b, 1, info )
1016  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
1017  infot = 7
1018  CALL zhpsv( 'U', 2, 0, a, ip, b, 1, info )
1019  CALL chkxer( 'ZHPSV ', infot, nout, lerr, ok )
1020 *
1021 * ZHPSVX
1022 *
1023  srnamt = 'ZHPSVX'
1024  infot = 1
1025  CALL zhpsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1026  $ r2, w, rw, info )
1027  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
1028  infot = 2
1029  CALL zhpsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1030  $ r2, w, rw, info )
1031  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
1032  infot = 3
1033  CALL zhpsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1034  $ r2, w, rw, info )
1035  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
1036  infot = 4
1037  CALL zhpsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1038  $ r2, w, rw, info )
1039  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
1040  infot = 9
1041  CALL zhpsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1042  $ r2, w, rw, info )
1043  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
1044  infot = 11
1045  CALL zhpsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1046  $ r2, w, rw, info )
1047  CALL chkxer( 'ZHPSVX', infot, nout, lerr, ok )
1048 *
1049  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
1050 *
1051 * ZSYSV
1052 *
1053  srnamt = 'ZSYSV '
1054  infot = 1
1055  CALL zsysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
1056  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
1057  infot = 2
1058  CALL zsysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
1059  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
1060  infot = 3
1061  CALL zsysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
1062  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
1063  infot = 8
1064  CALL zsysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
1065  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
1066  infot = 10
1067  CALL zsysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
1068  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
1069  infot = 10
1070  CALL zsysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
1071  CALL chkxer( 'ZSYSV ', infot, nout, lerr, ok )
1072 *
1073 * ZSYSVX
1074 *
1075  srnamt = 'ZSYSVX'
1076  infot = 1
1077  CALL zsysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
1078  $ rcond, r1, r2, w, 1, rw, info )
1079  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1080  infot = 2
1081  CALL zsysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
1082  $ rcond, r1, r2, w, 1, rw, info )
1083  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1084  infot = 3
1085  CALL zsysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
1086  $ rcond, r1, r2, w, 1, rw, info )
1087  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1088  infot = 4
1089  CALL zsysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
1090  $ rcond, r1, r2, w, 1, rw, info )
1091  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1092  infot = 6
1093  CALL zsysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
1094  $ rcond, r1, r2, w, 4, rw, info )
1095  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1096  infot = 8
1097  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
1098  $ rcond, r1, r2, w, 4, rw, info )
1099  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1100  infot = 11
1101  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
1102  $ rcond, r1, r2, w, 4, rw, info )
1103  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1104  infot = 13
1105  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
1106  $ rcond, r1, r2, w, 4, rw, info )
1107  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1108  infot = 18
1109  CALL zsysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
1110  $ rcond, r1, r2, w, 3, rw, info )
1111  CALL chkxer( 'ZSYSVX', infot, nout, lerr, ok )
1112 *
1113 * ZSYSVXX
1114 *
1115  n_err_bnds = 3
1116  nparams = 1
1117  srnamt = 'ZSYSVXX'
1118  infot = 1
1119  eq = 'N'
1120  CALL zsysvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
1121  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1122  $ err_bnds_c, nparams, params, w, rw, info )
1123  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1124  infot = 2
1125  CALL zsysvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
1126  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1127  $ err_bnds_c, nparams, params, w, rw, info )
1128  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1129  infot = 3
1130  CALL zsysvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
1131  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1132  $ err_bnds_c, nparams, params, w, rw, info )
1133  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1134  infot = 4
1135  eq = '/'
1136  CALL zsysvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, r, b, 1, x,
1137  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1138  $ err_bnds_c, nparams, params, w, rw, info )
1139  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1140  eq = 'Y'
1141  infot = 6
1142  CALL zsysvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, r, b, 2, x,
1143  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1144  $ err_bnds_c, nparams, params, w, rw, info )
1145  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1146  infot = 8
1147  CALL zsysvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, r, b, 2, x,
1148  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1149  $ err_bnds_c, nparams, params, w, rw, info )
1150  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1151  infot = 10
1152  CALL zsysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, 'A', r, b, 2, x,
1153  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1154  $ err_bnds_c, nparams, params, w, rw, info )
1155  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1156  infot = 11
1157  eq='Y'
1158  CALL zsysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
1159  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1160  $ err_bnds_c, nparams, params, w, rw, info )
1161  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1162  infot = 11
1163  eq='Y'
1164  r(1) = -one
1165  CALL zsysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
1166  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1167  $ err_bnds_c, nparams, params, w, rw, info )
1168  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1169  infot = 13
1170  eq = 'N'
1171  CALL zsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 1, x,
1172  $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1173  $ err_bnds_c, nparams, params, w, rw, info )
1174  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1175  infot = 15
1176  CALL zsysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
1177  $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1178  $ err_bnds_c, nparams, params, w, rw, info )
1179  CALL chkxer( 'ZSYSVXX', infot, nout, lerr, ok )
1180 *
1181  ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
1182 *
1183 * ZSYSV_ROOK
1184 *
1185  srnamt = 'ZSYSV_ROOK'
1186  infot = 1
1187  CALL zsysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
1188  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
1189  infot = 2
1190  CALL zsysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
1191  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
1192  infot = 3
1193  CALL zsysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
1194  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
1195  infot = 8
1196  CALL zsysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
1197  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
1198  infot = 10
1199  CALL zsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
1200  CALL chkxer( 'ZSYSV_ROOK', infot, nout, lerr, ok )
1201  infot = 10
1202  CALL zsysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
1203 *
1204  ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
1205 *
1206 * ZSYSV_RK
1207 *
1208 * Test error exits of the driver that uses factorization
1209 * of a symmetric indefinite matrix with rook
1210 * (bounded Bunch-Kaufman) pivoting with the new storage
1211 * format for factors L ( or U) and D.
1212 *
1213 * L (or U) is stored in A, diagonal of D is stored on the
1214 * diagonal of A, subdiagonal of D is stored in a separate array E.
1215 *
1216  srnamt = 'ZSYSV_RK'
1217  infot = 1
1218  CALL zsysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
1219  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
1220  infot = 2
1221  CALL zsysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
1222  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
1223  infot = 3
1224  CALL zsysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
1225  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
1226  infot = 5
1227  CALL zsysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
1228  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
1229  infot = 9
1230  CALL zsysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
1231  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
1232  infot = 11
1233  CALL zsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
1234  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
1235  infot = 11
1236  CALL zsysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
1237  CALL chkxer( 'ZSYSV_RK', infot, nout, lerr, ok )
1238 *
1239  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
1240 *
1241 * ZSPSV
1242 *
1243  srnamt = 'ZSPSV '
1244  infot = 1
1245  CALL zspsv( '/', 0, 0, a, ip, b, 1, info )
1246  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1247  infot = 2
1248  CALL zspsv( 'U', -1, 0, a, ip, b, 1, info )
1249  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1250  infot = 3
1251  CALL zspsv( 'U', 0, -1, a, ip, b, 1, info )
1252  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1253  infot = 7
1254  CALL zspsv( 'U', 2, 0, a, ip, b, 1, info )
1255  CALL chkxer( 'ZSPSV ', infot, nout, lerr, ok )
1256 *
1257 * ZSPSVX
1258 *
1259  srnamt = 'ZSPSVX'
1260  infot = 1
1261  CALL zspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1262  $ r2, w, rw, info )
1263  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1264  infot = 2
1265  CALL zspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1266  $ r2, w, rw, info )
1267  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1268  infot = 3
1269  CALL zspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1270  $ r2, w, rw, info )
1271  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1272  infot = 4
1273  CALL zspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1274  $ r2, w, rw, info )
1275  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1276  infot = 9
1277  CALL zspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1278  $ r2, w, rw, info )
1279  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1280  infot = 11
1281  CALL zspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1282  $ r2, w, rw, info )
1283  CALL chkxer( 'ZSPSVX', infot, nout, lerr, ok )
1284  END IF
1285 *
1286 * Print a summary line.
1287 *
1288  IF( ok ) THEN
1289  WRITE( nout, fmt = 9999 )path
1290  ELSE
1291  WRITE( nout, fmt = 9998 )path
1292  END IF
1293 *
1294  9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
1295  9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
1296  $ 'exits ***' )
1297 *
1298  RETURN
1299 *
1300 * End of ZERRVX
1301 *
1302  END
subroutine zgesvxx(FACT, TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, RPVGRW, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
ZGESVXX computes the solution to system of linear equations A * X = B for GE matrices ...
Definition: zgesvxx.f:542
subroutine zsysv_rk(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, WORK, LWORK, INFO)
ZSYSV_RK computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysv_rk.f:230
subroutine zhesv_rk(UPLO, N, NRHS, A, LDA, E, IPIV, B, LDB, WORK, LWORK, INFO)
ZHESV_RK computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zhesv_rk.f:230
subroutine zgbsv(N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
ZGBSV computes the solution to system of linear equations A * X = B for GB matrices (simple driver) ...
Definition: zgbsv.f:164
subroutine zgtsvx(FACT, TRANS, N, NRHS, DL, D, DU, DLF, DF, DUF, DU2, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZGTSVX computes the solution to system of linear equations A * X = B for GT matrices ...
Definition: zgtsvx.f:296
subroutine zsysv(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZSYSV computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysv.f:173
subroutine zsysvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK, RWORK, INFO)
ZSYSVX computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysvx.f:287
subroutine zhpsv(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
ZHPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zhpsv.f:164
subroutine zgbsvxx(FACT, TRANS, N, KL, KU, NRHS, AB, LDAB, AFB, LDAFB, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, RPVGRW, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
ZGBSVXX computes the solution to system of linear equations A * X = B for GB matrices ...
Definition: zgbsvxx.f:562
subroutine zposv(UPLO, N, NRHS, A, LDA, B, LDB, INFO)
ZPOSV computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: zposv.f:132
subroutine zppsvx(FACT, UPLO, N, NRHS, AP, AFP, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zppsvx.f:313
subroutine zgesv(N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZGESV computes the solution to system of linear equations A * X = B for GE matrices (simple driver) ...
Definition: zgesv.f:124
subroutine zhesvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, LWORK, RWORK, INFO)
ZHESVX computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: zhesvx.f:287
subroutine zpbsv(UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO)
ZPBSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zpbsv.f:166
subroutine zgbsvx(FACT, TRANS, N, KL, KU, NRHS, AB, LDAB, AFB, LDAFB, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZGBSVX computes the solution to system of linear equations A * X = B for GB matrices ...
Definition: zgbsvx.f:372
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
Definition: cblat2.f:3199
subroutine zsysvxx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED, S, B, LDB, X, LDX, RCOND, RPVGRW, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
ZSYSVXX computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysvxx.f:508
logical function lsamen(N, CA, CB)
LSAMEN
Definition: lsamen.f:76
subroutine zspsv(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
ZSPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zspsv.f:164
subroutine zptsvx(FACT, N, NRHS, D, E, DF, EF, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZPTSVX computes the solution to system of linear equations A * X = B for PT matrices ...
Definition: zptsvx.f:236
subroutine zgesvx(FACT, TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED, R, C, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZGESVX computes the solution to system of linear equations A * X = B for GE matrices ...
Definition: zgesvx.f:352
subroutine zhpsvx(FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZHPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zhpsvx.f:279
subroutine zhesvxx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, EQUED, S, B, LDB, X, LDX, RCOND, RPVGRW, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
ZHESVXX computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: zhesvxx.f:508
subroutine zerrvx(PATH, NUNIT)
ZERRVX
Definition: zerrvx.f:57
subroutine zppsv(UPLO, N, NRHS, AP, B, LDB, INFO)
ZPPSV computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zppsv.f:146
subroutine zspsvx(FACT, UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZSPSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zspsvx.f:279
subroutine zpbsvx(FACT, UPLO, N, KD, NRHS, AB, LDAB, AFB, LDAFB, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZPBSVX computes the solution to system of linear equations A * X = B for OTHER matrices ...
Definition: zpbsvx.f:344
subroutine zhesv_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZHESV_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using the ...
Definition: zhesv_rook.f:207
subroutine zposvxx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, EQUED, S, B, LDB, X, LDX, RCOND, RPVGRW, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
ZPOSVXX computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: zposvxx.f:495
subroutine zposvx(FACT, UPLO, N, NRHS, A, LDA, AF, LDAF, EQUED, S, B, LDB, X, LDX, RCOND, FERR, BERR, WORK, RWORK, INFO)
ZPOSVX computes the solution to system of linear equations A * X = B for PO matrices ...
Definition: zposvx.f:308
subroutine zhesv(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZHESV computes the solution to system of linear equations A * X = B for HE matrices ...
Definition: zhesv.f:173
subroutine zptsv(N, NRHS, D, E, B, LDB, INFO)
ZPTSV computes the solution to system of linear equations A * X = B for PT matrices ...
Definition: zptsv.f:117
subroutine zsysv_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
ZSYSV_ROOK computes the solution to system of linear equations A * X = B for SY matrices ...
Definition: zsysv_rook.f:206
subroutine zgtsv(N, NRHS, DL, D, DU, B, LDB, INFO)
ZGTSV computes the solution to system of linear equations A * X = B for GT matrices ...
Definition: zgtsv.f:126