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