LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cerrvx.f
Go to the documentation of this file.
1 *> \brief \b CERRVX
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 April 2012
52 *
53 *> \ingroup complex_lin
54 *
55 * =====================================================================
56  SUBROUTINE cerrvx( PATH, NUNIT )
57 *
58 * -- LAPACK test routine (version 3.4.1) --
59 * -- LAPACK is a software package provided by Univ. of Tennessee, --
60 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
61 * April 2012
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
78  REAL rcond
79 * ..
80 * .. Local Arrays ..
81  INTEGER ip( nmax )
82  REAL c( nmax ), r( nmax ), r1( nmax ), r2( nmax ),
83  $ rf( nmax ), rw( nmax )
84  COMPLEX a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
85  $ w( 2*nmax ), x( nmax )
86 * ..
87 * .. External Functions ..
88  LOGICAL lsamen
89  EXTERNAL lsamen
90 * ..
91 * .. External Subroutines ..
92  EXTERNAL cgbsv, cgbsvx, cgesv, cgesvx, cgtsv, cgtsvx,
95  $ cptsvx, cspsv, cspsvx, csysv,
96  $ csysvx
97 * ..
98 * .. Scalars in Common ..
99  LOGICAL lerr, ok
100  CHARACTER*32 srnamt
101  INTEGER infot, nout
102 * ..
103 * .. Common blocks ..
104  common / infoc / infot, nout, ok, lerr
105  common / srnamc / srnamt
106 * ..
107 * .. Intrinsic Functions ..
108  INTRINSIC cmplx, real
109 * ..
110 * .. Executable Statements ..
111 *
112  nout = nunit
113  WRITE( nout, fmt = * )
114  c2 = path( 2: 3 )
115 *
116 * Set the variables to innocuous values.
117 *
118  DO 20 j = 1, nmax
119  DO 10 i = 1, nmax
120  a( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
121  af( i, j ) = cmplx( 1. / REAL( I+J ), -1. / REAL( I+J ) )
122  10 continue
123  b( j ) = 0.
124  r1( j ) = 0.
125  r2( j ) = 0.
126  w( j ) = 0.
127  x( j ) = 0.
128  c( j ) = 0.
129  r( j ) = 0.
130  ip( j ) = j
131  20 continue
132  eq = ' '
133  ok = .true.
134 *
135  IF( lsamen( 2, c2, 'GE' ) ) THEN
136 *
137 * CGESV
138 *
139  srnamt = 'CGESV '
140  infot = 1
141  CALL cgesv( -1, 0, a, 1, ip, b, 1, info )
142  CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
143  infot = 2
144  CALL cgesv( 0, -1, a, 1, ip, b, 1, info )
145  CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
146  infot = 4
147  CALL cgesv( 2, 1, a, 1, ip, b, 2, info )
148  CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
149  infot = 7
150  CALL cgesv( 2, 1, a, 2, ip, b, 1, info )
151  CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
152 *
153 * CGESVX
154 *
155  srnamt = 'CGESVX'
156  infot = 1
157  CALL cgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
158  $ x, 1, rcond, r1, r2, w, rw, info )
159  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
160  infot = 2
161  CALL cgesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
162  $ x, 1, rcond, r1, r2, w, rw, info )
163  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
164  infot = 3
165  CALL cgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
166  $ x, 1, rcond, r1, r2, w, rw, info )
167  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
168  infot = 4
169  CALL cgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
170  $ x, 1, rcond, r1, r2, w, rw, info )
171  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
172  infot = 6
173  CALL cgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
174  $ x, 2, rcond, r1, r2, w, rw, info )
175  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
176  infot = 8
177  CALL cgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
178  $ x, 2, rcond, r1, r2, w, rw, info )
179  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
180  infot = 10
181  eq = '/'
182  CALL cgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
183  $ x, 1, rcond, r1, r2, w, rw, info )
184  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
185  infot = 11
186  eq = 'R'
187  CALL cgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
188  $ x, 1, rcond, r1, r2, w, rw, info )
189  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
190  infot = 12
191  eq = 'C'
192  CALL cgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
193  $ x, 1, rcond, r1, r2, w, rw, info )
194  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
195  infot = 14
196  CALL cgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
197  $ x, 2, rcond, r1, r2, w, rw, info )
198  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
199  infot = 16
200  CALL cgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
201  $ x, 1, rcond, r1, r2, w, rw, info )
202  CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
203 *
204  ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
205 *
206 * CGBSV
207 *
208  srnamt = 'CGBSV '
209  infot = 1
210  CALL cgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
211  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
212  infot = 2
213  CALL cgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
214  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
215  infot = 3
216  CALL cgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
217  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
218  infot = 4
219  CALL cgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
220  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
221  infot = 6
222  CALL cgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
223  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
224  infot = 9
225  CALL cgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
226  CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
227 *
228 * CGBSVX
229 *
230  srnamt = 'CGBSVX'
231  infot = 1
232  CALL cgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
233  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
234  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
235  infot = 2
236  CALL cgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
237  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
238  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
239  infot = 3
240  CALL cgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
241  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
242  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
243  infot = 4
244  CALL cgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
245  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
246  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
247  infot = 5
248  CALL cgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
249  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
250  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
251  infot = 6
252  CALL cgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
253  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
254  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
255  infot = 8
256  CALL cgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
257  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
258  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
259  infot = 10
260  CALL cgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
261  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
262  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
263  infot = 12
264  eq = '/'
265  CALL cgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
266  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
267  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
268  infot = 13
269  eq = 'R'
270  CALL cgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
271  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
272  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
273  infot = 14
274  eq = 'C'
275  CALL cgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
276  $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
277  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
278  infot = 16
279  CALL cgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
280  $ b, 1, x, 2, rcond, r1, r2, w, rw, info )
281  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
282  infot = 18
283  CALL cgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
284  $ b, 2, x, 1, rcond, r1, r2, w, rw, info )
285  CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
286 *
287  ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
288 *
289 * CGTSV
290 *
291  srnamt = 'CGTSV '
292  infot = 1
293  CALL cgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
294  $ info )
295  CALL chkxer( 'CGTSV ', infot, nout, lerr, ok )
296  infot = 2
297  CALL cgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
298  $ info )
299  CALL chkxer( 'CGTSV ', infot, nout, lerr, ok )
300  infot = 7
301  CALL cgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
302  CALL chkxer( 'CGTSV ', infot, nout, lerr, ok )
303 *
304 * CGTSVX
305 *
306  srnamt = 'CGTSVX'
307  infot = 1
308  CALL cgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
309  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
310  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
311  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
312  infot = 2
313  CALL cgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
314  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
315  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
316  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
317  infot = 3
318  CALL cgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
319  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
320  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
321  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
322  infot = 4
323  CALL cgtsvx( 'N', 'N', 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
324  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
325  $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
326  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
327  infot = 14
328  CALL cgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
329  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
330  $ ip, b, 1, x, 2, rcond, r1, r2, w, rw, info )
331  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
332  infot = 16
333  CALL cgtsvx( 'N', 'N', 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
334  $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
335  $ ip, b, 2, x, 1, rcond, r1, r2, w, rw, info )
336  CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
337 *
338  ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
339 *
340 * CPOSV
341 *
342  srnamt = 'CPOSV '
343  infot = 1
344  CALL cposv( '/', 0, 0, a, 1, b, 1, info )
345  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
346  infot = 2
347  CALL cposv( 'U', -1, 0, a, 1, b, 1, info )
348  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
349  infot = 3
350  CALL cposv( 'U', 0, -1, a, 1, b, 1, info )
351  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
352  infot = 5
353  CALL cposv( 'U', 2, 0, a, 1, b, 2, info )
354  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
355  infot = 7
356  CALL cposv( 'U', 2, 0, a, 2, b, 1, info )
357  CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
358 *
359 * CPOSVX
360 *
361  srnamt = 'CPOSVX'
362  infot = 1
363  CALL cposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
364  $ rcond, r1, r2, w, rw, info )
365  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
366  infot = 2
367  CALL cposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
368  $ rcond, r1, r2, w, rw, info )
369  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
370  infot = 3
371  CALL cposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
372  $ rcond, r1, r2, w, rw, info )
373  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
374  infot = 4
375  CALL cposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
376  $ rcond, r1, r2, w, rw, info )
377  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
378  infot = 6
379  CALL cposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
380  $ rcond, r1, r2, w, rw, info )
381  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
382  infot = 8
383  CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
384  $ rcond, r1, r2, w, rw, info )
385  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
386  infot = 9
387  eq = '/'
388  CALL cposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
389  $ rcond, r1, r2, w, rw, info )
390  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
391  infot = 10
392  eq = 'Y'
393  CALL cposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
394  $ rcond, r1, r2, w, rw, info )
395  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
396  infot = 12
397  CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
398  $ rcond, r1, r2, w, rw, info )
399  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
400  infot = 14
401  CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
402  $ rcond, r1, r2, w, rw, info )
403  CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
404 *
405  ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
406 *
407 * CPPSV
408 *
409  srnamt = 'CPPSV '
410  infot = 1
411  CALL cppsv( '/', 0, 0, a, b, 1, info )
412  CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
413  infot = 2
414  CALL cppsv( 'U', -1, 0, a, b, 1, info )
415  CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
416  infot = 3
417  CALL cppsv( 'U', 0, -1, a, b, 1, info )
418  CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
419  infot = 6
420  CALL cppsv( 'U', 2, 0, a, b, 1, info )
421  CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
422 *
423 * CPPSVX
424 *
425  srnamt = 'CPPSVX'
426  infot = 1
427  CALL cppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
428  $ r1, r2, w, rw, info )
429  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
430  infot = 2
431  CALL cppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
432  $ r1, r2, w, rw, info )
433  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
434  infot = 3
435  CALL cppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
436  $ r1, r2, w, rw, info )
437  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
438  infot = 4
439  CALL cppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
440  $ r1, r2, w, rw, info )
441  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
442  infot = 7
443  eq = '/'
444  CALL cppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
445  $ r1, r2, w, rw, info )
446  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
447  infot = 8
448  eq = 'Y'
449  CALL cppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
450  $ r1, r2, w, rw, info )
451  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
452  infot = 10
453  CALL cppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
454  $ r1, r2, w, rw, info )
455  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
456  infot = 12
457  CALL cppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
458  $ r1, r2, w, rw, info )
459  CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
460 *
461  ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
462 *
463 * CPBSV
464 *
465  srnamt = 'CPBSV '
466  infot = 1
467  CALL cpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
468  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
469  infot = 2
470  CALL cpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
471  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
472  infot = 3
473  CALL cpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
474  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
475  infot = 4
476  CALL cpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
477  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
478  infot = 6
479  CALL cpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
480  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
481  infot = 8
482  CALL cpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
483  CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
484 *
485 * CPBSVX
486 *
487  srnamt = 'CPBSVX'
488  infot = 1
489  CALL cpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
490  $ rcond, r1, r2, w, rw, info )
491  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
492  infot = 2
493  CALL cpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
494  $ rcond, r1, r2, w, rw, info )
495  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
496  infot = 3
497  CALL cpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
498  $ 1, rcond, r1, r2, w, rw, info )
499  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
500  infot = 4
501  CALL cpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
502  $ 1, rcond, r1, r2, w, rw, info )
503  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
504  infot = 5
505  CALL cpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
506  $ 1, rcond, r1, r2, w, rw, info )
507  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
508  infot = 7
509  CALL cpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
510  $ rcond, r1, r2, w, rw, info )
511  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
512  infot = 9
513  CALL cpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
514  $ rcond, r1, r2, w, rw, info )
515  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
516  infot = 10
517  eq = '/'
518  CALL cpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
519  $ rcond, r1, r2, w, rw, info )
520  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
521  infot = 11
522  eq = 'Y'
523  CALL cpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
524  $ rcond, r1, r2, w, rw, info )
525  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
526  infot = 13
527  CALL cpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
528  $ rcond, r1, r2, w, rw, info )
529  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
530  infot = 15
531  CALL cpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
532  $ rcond, r1, r2, w, rw, info )
533  CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
534 *
535  ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
536 *
537 * CPTSV
538 *
539  srnamt = 'CPTSV '
540  infot = 1
541  CALL cptsv( -1, 0, r, a( 1, 1 ), b, 1, info )
542  CALL chkxer( 'CPTSV ', infot, nout, lerr, ok )
543  infot = 2
544  CALL cptsv( 0, -1, r, a( 1, 1 ), b, 1, info )
545  CALL chkxer( 'CPTSV ', infot, nout, lerr, ok )
546  infot = 6
547  CALL cptsv( 2, 0, r, a( 1, 1 ), b, 1, info )
548  CALL chkxer( 'CPTSV ', infot, nout, lerr, ok )
549 *
550 * CPTSVX
551 *
552  srnamt = 'CPTSVX'
553  infot = 1
554  CALL cptsvx( '/', 0, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
555  $ 1, rcond, r1, r2, w, rw, info )
556  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
557  infot = 2
558  CALL cptsvx( 'N', -1, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
559  $ 1, rcond, r1, r2, w, rw, info )
560  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
561  infot = 3
562  CALL cptsvx( 'N', 0, -1, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
563  $ 1, rcond, r1, r2, w, rw, info )
564  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
565  infot = 9
566  CALL cptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
567  $ 2, rcond, r1, r2, w, rw, info )
568  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
569  infot = 11
570  CALL cptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 2, x,
571  $ 1, rcond, r1, r2, w, rw, info )
572  CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
573 *
574  ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
575 *
576 * CHESV
577 *
578  srnamt = 'CHESV '
579  infot = 1
580  CALL chesv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
581  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
582  infot = 2
583  CALL chesv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
584  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
585  infot = 3
586  CALL chesv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
587  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
588  infot = 5
589  CALL chesv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
590  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
591  infot = 8
592  CALL chesv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
593  CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
594 *
595 * CHESVX
596 *
597  srnamt = 'CHESVX'
598  infot = 1
599  CALL chesvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
600  $ rcond, r1, r2, w, 1, rw, info )
601  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
602  infot = 2
603  CALL chesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
604  $ rcond, r1, r2, w, 1, rw, info )
605  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
606  infot = 3
607  CALL chesvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
608  $ rcond, r1, r2, w, 1, rw, info )
609  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
610  infot = 4
611  CALL chesvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
612  $ rcond, r1, r2, w, 1, rw, info )
613  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
614  infot = 6
615  CALL chesvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
616  $ rcond, r1, r2, w, 4, rw, info )
617  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
618  infot = 8
619  CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
620  $ rcond, r1, r2, w, 4, rw, info )
621  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
622  infot = 11
623  CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
624  $ rcond, r1, r2, w, 4, rw, info )
625  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
626  infot = 13
627  CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
628  $ rcond, r1, r2, w, 4, rw, info )
629  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
630  infot = 18
631  CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
632  $ rcond, r1, r2, w, 3, rw, info )
633  CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
634 *
635  ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
636 *
637 * CHPSV
638 *
639  srnamt = 'CHPSV '
640  infot = 1
641  CALL chpsv( '/', 0, 0, a, ip, b, 1, info )
642  CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
643  infot = 2
644  CALL chpsv( 'U', -1, 0, a, ip, b, 1, info )
645  CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
646  infot = 3
647  CALL chpsv( 'U', 0, -1, a, ip, b, 1, info )
648  CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
649  infot = 7
650  CALL chpsv( 'U', 2, 0, a, ip, b, 1, info )
651  CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
652 *
653 * CHPSVX
654 *
655  srnamt = 'CHPSVX'
656  infot = 1
657  CALL chpsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
658  $ r2, w, rw, info )
659  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
660  infot = 2
661  CALL chpsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
662  $ r2, w, rw, info )
663  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
664  infot = 3
665  CALL chpsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
666  $ r2, w, rw, info )
667  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
668  infot = 4
669  CALL chpsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
670  $ r2, w, rw, info )
671  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
672  infot = 9
673  CALL chpsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
674  $ r2, w, rw, info )
675  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
676  infot = 11
677  CALL chpsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
678  $ r2, w, rw, info )
679  CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
680 *
681  ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
682 *
683 * CSYSV
684 *
685  srnamt = 'CSYSV '
686  infot = 1
687  CALL csysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
688  CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
689  infot = 2
690  CALL csysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
691  CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
692  infot = 3
693  CALL csysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
694  CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
695  infot = 8
696  CALL csysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
697  CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
698 *
699 * CSYSVX
700 *
701  srnamt = 'CSYSVX'
702  infot = 1
703  CALL csysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
704  $ rcond, r1, r2, w, 1, rw, info )
705  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
706  infot = 2
707  CALL csysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
708  $ rcond, r1, r2, w, 1, rw, info )
709  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
710  infot = 3
711  CALL csysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
712  $ rcond, r1, r2, w, 1, rw, info )
713  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
714  infot = 4
715  CALL csysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
716  $ rcond, r1, r2, w, 1, rw, info )
717  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
718  infot = 6
719  CALL csysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
720  $ rcond, r1, r2, w, 4, rw, info )
721  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
722  infot = 8
723  CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
724  $ rcond, r1, r2, w, 4, rw, info )
725  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
726  infot = 11
727  CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
728  $ rcond, r1, r2, w, 4, rw, info )
729  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
730  infot = 13
731  CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
732  $ rcond, r1, r2, w, 4, rw, info )
733  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
734  infot = 18
735  CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
736  $ rcond, r1, r2, w, 3, rw, info )
737  CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
738 *
739  ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
740 *
741 * CSPSV
742 *
743  srnamt = 'CSPSV '
744  infot = 1
745  CALL cspsv( '/', 0, 0, a, ip, b, 1, info )
746  CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
747  infot = 2
748  CALL cspsv( 'U', -1, 0, a, ip, b, 1, info )
749  CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
750  infot = 3
751  CALL cspsv( 'U', 0, -1, a, ip, b, 1, info )
752  CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
753  infot = 7
754  CALL cspsv( 'U', 2, 0, a, ip, b, 1, info )
755  CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
756 *
757 * CSPSVX
758 *
759  srnamt = 'CSPSVX'
760  infot = 1
761  CALL cspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
762  $ r2, w, rw, info )
763  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
764  infot = 2
765  CALL cspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
766  $ r2, w, rw, info )
767  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
768  infot = 3
769  CALL cspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
770  $ r2, w, rw, info )
771  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
772  infot = 4
773  CALL cspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
774  $ r2, w, rw, info )
775  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
776  infot = 9
777  CALL cspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
778  $ r2, w, rw, info )
779  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
780  infot = 11
781  CALL cspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
782  $ r2, w, rw, info )
783  CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
784  END IF
785 *
786 * Print a summary line.
787 *
788  IF( ok ) THEN
789  WRITE( nout, fmt = 9999 )path
790  ELSE
791  WRITE( nout, fmt = 9998 )path
792  END IF
793 *
794  9999 format( 1x, a3, ' drivers passed the tests of the error exits' )
795  9998 format( ' *** ', a3, ' drivers failed the tests of the error ',
796  $ 'exits ***' )
797 *
798  return
799 *
800 * End of CERRVX
801 *
802  END