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