LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
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*> \ingroup complex_lin
52*
53* =====================================================================
54 SUBROUTINE cerrvx( PATH, NUNIT )
55*
56* -- LAPACK test routine --
57* -- LAPACK is a software package provided by Univ. of Tennessee, --
58* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
59*
60* .. Scalar Arguments ..
61 CHARACTER*3 PATH
62 INTEGER NUNIT
63* ..
64*
65* =====================================================================
66*
67* .. Parameters ..
68 INTEGER NMAX
69 parameter( nmax = 4 )
70 REAL ONE
71 parameter( one = 1.0e+0 )
72* ..
73* .. Local Scalars ..
74 CHARACTER EQ
75 CHARACTER*2 C2
76 INTEGER I, INFO, J, N_ERR_BNDS, NPARAMS
77 REAL RCOND, RPVGRW, BERR
78* ..
79* .. Local Arrays ..
80 INTEGER IP( NMAX )
81 REAL C( NMAX ), R( NMAX ), R1( NMAX ), R2( NMAX ),
82 $ RF( NMAX ), RW( NMAX ), ERR_BNDS_N( NMAX, 3 ),
83 $ ERR_BNDS_C( NMAX, 3 ), PARAMS( 1 )
84 COMPLEX A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
85 $ E( NMAX ), 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,
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.e+0
125 e( j ) = 0e+0
126 r1( j ) = 0.e+0
127 r2( j ) = 0.e+0
128 w( j ) = 0.e+0
129 x( j ) = 0.e+0
130 c( j ) = 0.e+0
131 r( j ) = 0.e+0
132 ip( j ) = j
133 20 CONTINUE
134 eq = ' '
135 ok = .true.
136*
137 IF( lsamen( 2, c2, 'GE' ) ) THEN
138*
139* CGESV
140*
141 srnamt = 'CGESV '
142 infot = 1
143 CALL cgesv( -1, 0, a, 1, ip, b, 1, info )
144 CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
145 infot = 2
146 CALL cgesv( 0, -1, a, 1, ip, b, 1, info )
147 CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
148 infot = 4
149 CALL cgesv( 2, 1, a, 1, ip, b, 2, info )
150 CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
151 infot = 7
152 CALL cgesv( 2, 1, a, 2, ip, b, 1, info )
153 CALL chkxer( 'CGESV ', infot, nout, lerr, ok )
154*
155* CGESVX
156*
157 srnamt = 'CGESVX'
158 infot = 1
159 CALL cgesvx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
160 $ x, 1, rcond, r1, r2, w, rw, info )
161 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
162 infot = 2
163 CALL cgesvx( '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( 'CGESVX', infot, nout, lerr, ok )
166 infot = 3
167 CALL cgesvx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
168 $ x, 1, rcond, r1, r2, w, rw, info )
169 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
170 infot = 4
171 CALL cgesvx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
172 $ x, 1, rcond, r1, r2, w, rw, info )
173 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
174 infot = 6
175 CALL cgesvx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
176 $ x, 2, rcond, r1, r2, w, rw, info )
177 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
178 infot = 8
179 CALL cgesvx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
180 $ x, 2, rcond, r1, r2, w, rw, info )
181 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
182 infot = 10
183 eq = '/'
184 CALL cgesvx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
185 $ x, 1, rcond, r1, r2, w, rw, info )
186 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
187 infot = 11
188 eq = 'R'
189 CALL cgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
190 $ x, 1, rcond, r1, r2, w, rw, info )
191 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
192 infot = 12
193 eq = 'C'
194 CALL cgesvx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
195 $ x, 1, rcond, r1, r2, w, rw, info )
196 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
197 infot = 14
198 CALL cgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
199 $ x, 2, rcond, r1, r2, w, rw, info )
200 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
201 infot = 16
202 CALL cgesvx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
203 $ x, 1, rcond, r1, r2, w, rw, info )
204 CALL chkxer( 'CGESVX', infot, nout, lerr, ok )
205*
206* CGESVXX
207*
208 n_err_bnds = 3
209 nparams = 1
210 srnamt = 'CGESVXX'
211 infot = 1
212 CALL cgesvxx( '/', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
213 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
214 $ err_bnds_c, nparams, params, w, rw, info )
215 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
216 infot = 2
217 CALL cgesvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
218 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
219 $ err_bnds_c, nparams, params, w, rw, info )
220 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
221 infot = 3
222 CALL cgesvxx( 'N', 'N', -1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
223 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
224 $ err_bnds_c, nparams, params, w, rw, info )
225 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
226 infot = 4
227 CALL cgesvxx( 'N', 'N', 0, -1, a, 1, af, 1, ip, eq, r, c, b, 1,
228 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
229 $ err_bnds_c, nparams, params, w, rw, info )
230 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
231 infot = 6
232 CALL cgesvxx( 'N', 'N', 2, 1, a, 1, af, 2, ip, eq, r, c, b, 2,
233 $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
234 $ err_bnds_c, nparams, params, w, rw, info )
235 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
236 infot = 8
237 CALL cgesvxx( 'N', 'N', 2, 1, a, 2, af, 1, ip, eq, r, c, b, 2,
238 $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
239 $ err_bnds_c, nparams, params, w, rw, info )
240 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
241 infot = 10
242 eq = '/'
243 CALL cgesvxx( 'F', 'N', 0, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
244 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
245 $ err_bnds_c, nparams, params, w, rw, info )
246 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
247 infot = 11
248 eq = 'R'
249 CALL cgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
250 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
251 $ err_bnds_c, nparams, params, w, rw, info )
252 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
253 infot = 12
254 eq = 'C'
255 CALL cgesvxx( 'F', 'N', 1, 0, a, 1, af, 1, ip, eq, r, c, b, 1,
256 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
257 $ err_bnds_c, nparams, params, w, rw, info )
258 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
259 infot = 14
260 CALL cgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 1,
261 $ x, 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
262 $ err_bnds_c, nparams, params, w, rw, info )
263 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
264 infot = 16
265 CALL cgesvxx( 'N', 'N', 2, 1, a, 2, af, 2, ip, eq, r, c, b, 2,
266 $ x, 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
267 $ err_bnds_c, nparams, params, w, rw, info )
268 CALL chkxer( 'CGESVXX', infot, nout, lerr, ok )
269*
270 ELSE IF( lsamen( 2, c2, 'GB' ) ) THEN
271*
272* CGBSV
273*
274 srnamt = 'CGBSV '
275 infot = 1
276 CALL cgbsv( -1, 0, 0, 0, a, 1, ip, b, 1, info )
277 CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
278 infot = 2
279 CALL cgbsv( 1, -1, 0, 0, a, 1, ip, b, 1, info )
280 CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
281 infot = 3
282 CALL cgbsv( 1, 0, -1, 0, a, 1, ip, b, 1, info )
283 CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
284 infot = 4
285 CALL cgbsv( 0, 0, 0, -1, a, 1, ip, b, 1, info )
286 CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
287 infot = 6
288 CALL cgbsv( 1, 1, 1, 0, a, 3, ip, b, 1, info )
289 CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
290 infot = 9
291 CALL cgbsv( 2, 0, 0, 0, a, 1, ip, b, 1, info )
292 CALL chkxer( 'CGBSV ', infot, nout, lerr, ok )
293*
294* CGBSVX
295*
296 srnamt = 'CGBSVX'
297 infot = 1
298 CALL cgbsvx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
299 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
300 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
301 infot = 2
302 CALL cgbsvx( 'N', '/', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
303 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
304 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
305 infot = 3
306 CALL cgbsvx( 'N', 'N', -1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
307 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
308 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
309 infot = 4
310 CALL cgbsvx( 'N', 'N', 1, -1, 0, 0, a, 1, af, 1, ip, eq, r, c,
311 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
312 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
313 infot = 5
314 CALL cgbsvx( 'N', 'N', 1, 0, -1, 0, a, 1, af, 1, ip, eq, r, c,
315 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
316 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
317 infot = 6
318 CALL cgbsvx( 'N', 'N', 0, 0, 0, -1, a, 1, af, 1, ip, eq, r, c,
319 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
320 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
321 infot = 8
322 CALL cgbsvx( 'N', 'N', 1, 1, 1, 0, a, 2, af, 4, ip, eq, r, c,
323 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
324 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
325 infot = 10
326 CALL cgbsvx( 'N', 'N', 1, 1, 1, 0, a, 3, af, 3, ip, eq, r, c,
327 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
328 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
329 infot = 12
330 eq = '/'
331 CALL cgbsvx( 'F', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
332 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
333 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
334 infot = 13
335 eq = 'R'
336 CALL cgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
337 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
338 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
339 infot = 14
340 eq = 'C'
341 CALL cgbsvx( 'F', 'N', 1, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
342 $ b, 1, x, 1, rcond, r1, r2, w, rw, info )
343 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
344 infot = 16
345 CALL cgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
346 $ b, 1, x, 2, rcond, r1, r2, w, rw, info )
347 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
348 infot = 18
349 CALL cgbsvx( 'N', 'N', 2, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
350 $ b, 2, x, 1, rcond, r1, r2, w, rw, info )
351 CALL chkxer( 'CGBSVX', infot, nout, lerr, ok )
352*
353* CGBSVXX
354*
355 n_err_bnds = 3
356 nparams = 1
357 srnamt = 'CGBSVXX'
358 infot = 1
359 CALL cgbsvxx( '/', 'N', 0, 0, 0, 0, a, 1, af, 1, ip, eq, r, c,
360 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
361 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
362 $ info )
363 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
364 infot = 2
365 CALL cgbsvxx( 'N', '/', 0, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
366 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
367 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
368 $ info )
369 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
370 infot = 3
371 CALL cgbsvxx( 'N', 'N', -1, 1, 1, 0, a, 1, af, 1, ip, eq, r, c,
372 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
373 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
374 $ info )
375 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
376 infot = 4
377 CALL cgbsvxx( 'N', 'N', 2, -1, 1, 0, a, 1, af, 1, ip, eq,
378 $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
379 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
380 $ info )
381 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
382 infot = 5
383 CALL cgbsvxx( 'N', 'N', 2, 1, -1, 0, a, 1, af, 1, ip, eq,
384 $ r, c, b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
385 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
386 $ info )
387 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
388 infot = 6
389 CALL cgbsvxx( 'N', 'N', 0, 1, 1, -1, a, 1, af, 1, ip, eq, r, c,
390 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
391 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
392 $ info )
393 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
394 infot = 8
395 CALL cgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 2, af, 2, ip, eq, r, c,
396 $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
397 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
398 $ info )
399 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
400 infot = 10
401 CALL cgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 3, ip, eq, r, c,
402 $ b, 2, x, 2, rcond, rpvgrw, berr, n_err_bnds,
403 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
404 $ info )
405 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
406 infot = 12
407 eq = '/'
408 CALL cgbsvxx( 'F', 'N', 0, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
409 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
410 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
411 $ info )
412 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
413 infot = 13
414 eq = 'R'
415 CALL cgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
416 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
417 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
418 $ info )
419 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
420 infot = 14
421 eq = 'C'
422 CALL cgbsvxx( 'F', 'N', 1, 1, 1, 0, a, 3, af, 4, ip, eq, r, c,
423 $ b, 1, x, 1, rcond, rpvgrw, berr, n_err_bnds,
424 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
425 $ info )
426 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
427 infot = 15
428 CALL cgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
429 $ b, 1, x, 2, rcond, rpvgrw, berr, n_err_bnds,
430 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
431 $ info )
432 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
433 infot = 16
434 CALL cgbsvxx( 'N', 'N', 2, 1, 1, 1, a, 3, af, 4, ip, eq, r, c,
435 $ b, 2, x, 1, rcond, rpvgrw, berr, n_err_bnds,
436 $ err_bnds_n, err_bnds_c, nparams, params, w, rw,
437 $ info )
438 CALL chkxer( 'CGBSVXX', infot, nout, lerr, ok )
439*
440 ELSE IF( lsamen( 2, c2, 'GT' ) ) THEN
441*
442* CGTSV
443*
444 srnamt = 'CGTSV '
445 infot = 1
446 CALL cgtsv( -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
447 $ info )
448 CALL chkxer( 'CGTSV ', infot, nout, lerr, ok )
449 infot = 2
450 CALL cgtsv( 0, -1, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1,
451 $ info )
452 CALL chkxer( 'CGTSV ', infot, nout, lerr, ok )
453 infot = 7
454 CALL cgtsv( 2, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ), b, 1, info )
455 CALL chkxer( 'CGTSV ', infot, nout, lerr, ok )
456*
457* CGTSVX
458*
459 srnamt = 'CGTSVX'
460 infot = 1
461 CALL cgtsvx( '/', 'N', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
462 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
463 $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
464 CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
465 infot = 2
466 CALL cgtsvx( 'N', '/', 0, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
467 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
468 $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
469 CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
470 infot = 3
471 CALL cgtsvx( 'N', 'N', -1, 0, a( 1, 1 ), a( 1, 2 ), a( 1, 3 ),
472 $ af( 1, 1 ), af( 1, 2 ), af( 1, 3 ), af( 1, 4 ),
473 $ ip, b, 1, x, 1, rcond, r1, r2, w, rw, info )
474 CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
475 infot = 4
476 CALL cgtsvx( 'N', 'N', 0, -1, 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( 'CGTSVX', infot, nout, lerr, ok )
480 infot = 14
481 CALL cgtsvx( 'N', 'N', 2, 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, 2, rcond, r1, r2, w, rw, info )
484 CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
485 infot = 16
486 CALL cgtsvx( 'N', 'N', 2, 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, 2, x, 1, rcond, r1, r2, w, rw, info )
489 CALL chkxer( 'CGTSVX', infot, nout, lerr, ok )
490*
491 ELSE IF( lsamen( 2, c2, 'PO' ) ) THEN
492*
493* CPOSV
494*
495 srnamt = 'CPOSV '
496 infot = 1
497 CALL cposv( '/', 0, 0, a, 1, b, 1, info )
498 CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
499 infot = 2
500 CALL cposv( 'U', -1, 0, a, 1, b, 1, info )
501 CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
502 infot = 3
503 CALL cposv( 'U', 0, -1, a, 1, b, 1, info )
504 CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
505 infot = 5
506 CALL cposv( 'U', 2, 0, a, 1, b, 2, info )
507 CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
508 infot = 7
509 CALL cposv( 'U', 2, 0, a, 2, b, 1, info )
510 CALL chkxer( 'CPOSV ', infot, nout, lerr, ok )
511*
512* CPOSVX
513*
514 srnamt = 'CPOSVX'
515 infot = 1
516 CALL cposvx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
517 $ rcond, r1, r2, w, rw, info )
518 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
519 infot = 2
520 CALL cposvx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
521 $ rcond, r1, r2, w, rw, info )
522 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
523 infot = 3
524 CALL cposvx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
525 $ rcond, r1, r2, w, rw, info )
526 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
527 infot = 4
528 CALL cposvx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
529 $ rcond, r1, r2, w, rw, info )
530 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
531 infot = 6
532 CALL cposvx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
533 $ rcond, r1, r2, w, rw, info )
534 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
535 infot = 8
536 CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
537 $ rcond, r1, r2, w, rw, info )
538 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
539 infot = 9
540 eq = '/'
541 CALL cposvx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
542 $ rcond, r1, r2, w, rw, info )
543 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
544 infot = 10
545 eq = 'Y'
546 CALL cposvx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
547 $ rcond, r1, r2, w, rw, info )
548 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
549 infot = 12
550 CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
551 $ rcond, r1, r2, w, rw, info )
552 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
553 infot = 14
554 CALL cposvx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
555 $ rcond, r1, r2, w, rw, info )
556 CALL chkxer( 'CPOSVX', infot, nout, lerr, ok )
557*
558* CPOSVXX
559*
560 n_err_bnds = 3
561 nparams = 1
562 srnamt = 'CPOSVXX'
563 infot = 1
564 CALL cposvxx( '/', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
565 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
566 $ err_bnds_c, nparams, params, w, rw, info )
567 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
568 infot = 2
569 CALL cposvxx( 'N', '/', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
570 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
571 $ err_bnds_c, nparams, params, w, rw, info )
572 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
573 infot = 3
574 CALL cposvxx( 'N', 'U', -1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
575 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
576 $ err_bnds_c, nparams, params, w, rw, info )
577 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
578 infot = 4
579 CALL cposvxx( 'N', 'U', 0, -1, a, 1, af, 1, eq, c, b, 1, x, 1,
580 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
581 $ err_bnds_c, nparams, params, w, rw, info )
582 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
583 infot = 6
584 CALL cposvxx( 'N', 'U', 2, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
585 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
586 $ err_bnds_c, nparams, params, w, rw, info )
587 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
588 infot = 8
589 CALL cposvxx( 'N', 'U', 2, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
590 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
591 $ err_bnds_c, nparams, params, w, rw, info )
592 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
593 infot = 9
594 eq = '/'
595 CALL cposvxx( 'F', 'U', 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
596 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
597 $ err_bnds_c, nparams, params, w, rw, info )
598 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
599 infot = 10
600 eq = 'Y'
601 CALL cposvxx( 'F', 'U', 1, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
602 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
603 $ err_bnds_c, nparams, params, w, rw, info )
604 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
605 infot = 12
606 CALL cposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 1, x, 2,
607 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
608 $ err_bnds_c, nparams, params, w, rw, info )
609 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
610 infot = 14
611 CALL cposvxx( 'N', 'U', 2, 0, a, 2, af, 2, eq, c, b, 2, x, 1,
612 $ rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
613 $ err_bnds_c, nparams, params, w, rw, info )
614 CALL chkxer( 'CPOSVXX', infot, nout, lerr, ok )
615*
616 ELSE IF( lsamen( 2, c2, 'PP' ) ) THEN
617*
618* CPPSV
619*
620 srnamt = 'CPPSV '
621 infot = 1
622 CALL cppsv( '/', 0, 0, a, b, 1, info )
623 CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
624 infot = 2
625 CALL cppsv( 'U', -1, 0, a, b, 1, info )
626 CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
627 infot = 3
628 CALL cppsv( 'U', 0, -1, a, b, 1, info )
629 CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
630 infot = 6
631 CALL cppsv( 'U', 2, 0, a, b, 1, info )
632 CALL chkxer( 'CPPSV ', infot, nout, lerr, ok )
633*
634* CPPSVX
635*
636 srnamt = 'CPPSVX'
637 infot = 1
638 CALL cppsvx( '/', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
639 $ r1, r2, w, rw, info )
640 CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
641 infot = 2
642 CALL cppsvx( 'N', '/', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
643 $ r1, r2, w, rw, info )
644 CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
645 infot = 3
646 CALL cppsvx( 'N', 'U', -1, 0, a, af, eq, c, b, 1, x, 1, rcond,
647 $ r1, r2, w, rw, info )
648 CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
649 infot = 4
650 CALL cppsvx( 'N', 'U', 0, -1, a, af, eq, c, b, 1, x, 1, rcond,
651 $ r1, r2, w, rw, info )
652 CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
653 infot = 7
654 eq = '/'
655 CALL cppsvx( 'F', 'U', 0, 0, a, af, eq, c, b, 1, x, 1, rcond,
656 $ r1, r2, w, rw, info )
657 CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
658 infot = 8
659 eq = 'Y'
660 CALL cppsvx( 'F', 'U', 1, 0, a, af, eq, c, b, 1, x, 1, rcond,
661 $ r1, r2, w, rw, info )
662 CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
663 infot = 10
664 CALL cppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 1, x, 2, rcond,
665 $ r1, r2, w, rw, info )
666 CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
667 infot = 12
668 CALL cppsvx( 'N', 'U', 2, 0, a, af, eq, c, b, 2, x, 1, rcond,
669 $ r1, r2, w, rw, info )
670 CALL chkxer( 'CPPSVX', infot, nout, lerr, ok )
671*
672 ELSE IF( lsamen( 2, c2, 'PB' ) ) THEN
673*
674* CPBSV
675*
676 srnamt = 'CPBSV '
677 infot = 1
678 CALL cpbsv( '/', 0, 0, 0, a, 1, b, 1, info )
679 CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
680 infot = 2
681 CALL cpbsv( 'U', -1, 0, 0, a, 1, b, 1, info )
682 CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
683 infot = 3
684 CALL cpbsv( 'U', 1, -1, 0, a, 1, b, 1, info )
685 CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
686 infot = 4
687 CALL cpbsv( 'U', 0, 0, -1, a, 1, b, 1, info )
688 CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
689 infot = 6
690 CALL cpbsv( 'U', 1, 1, 0, a, 1, b, 2, info )
691 CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
692 infot = 8
693 CALL cpbsv( 'U', 2, 0, 0, a, 1, b, 1, info )
694 CALL chkxer( 'CPBSV ', infot, nout, lerr, ok )
695*
696* CPBSVX
697*
698 srnamt = 'CPBSVX'
699 infot = 1
700 CALL cpbsvx( '/', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
701 $ rcond, r1, r2, w, rw, info )
702 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
703 infot = 2
704 CALL cpbsvx( 'N', '/', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
705 $ rcond, r1, r2, w, rw, info )
706 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
707 infot = 3
708 CALL cpbsvx( 'N', 'U', -1, 0, 0, a, 1, af, 1, eq, c, b, 1, x,
709 $ 1, rcond, r1, r2, w, rw, info )
710 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
711 infot = 4
712 CALL cpbsvx( 'N', 'U', 1, -1, 0, a, 1, af, 1, eq, c, b, 1, x,
713 $ 1, rcond, r1, r2, w, rw, info )
714 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
715 infot = 5
716 CALL cpbsvx( 'N', 'U', 0, 0, -1, a, 1, af, 1, eq, c, b, 1, x,
717 $ 1, rcond, r1, r2, w, rw, info )
718 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
719 infot = 7
720 CALL cpbsvx( 'N', 'U', 1, 1, 0, a, 1, af, 2, eq, c, b, 2, x, 2,
721 $ rcond, r1, r2, w, rw, info )
722 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
723 infot = 9
724 CALL cpbsvx( 'N', 'U', 1, 1, 0, a, 2, af, 1, eq, c, b, 2, x, 2,
725 $ rcond, r1, r2, w, rw, info )
726 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
727 infot = 10
728 eq = '/'
729 CALL cpbsvx( 'F', 'U', 0, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
730 $ rcond, r1, r2, w, rw, info )
731 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
732 infot = 11
733 eq = 'Y'
734 CALL cpbsvx( 'F', 'U', 1, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 1,
735 $ rcond, r1, r2, w, rw, info )
736 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
737 infot = 13
738 CALL cpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 1, x, 2,
739 $ rcond, r1, r2, w, rw, info )
740 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
741 infot = 15
742 CALL cpbsvx( 'N', 'U', 2, 0, 0, a, 1, af, 1, eq, c, b, 2, x, 1,
743 $ rcond, r1, r2, w, rw, info )
744 CALL chkxer( 'CPBSVX', infot, nout, lerr, ok )
745*
746 ELSE IF( lsamen( 2, c2, 'PT' ) ) THEN
747*
748* CPTSV
749*
750 srnamt = 'CPTSV '
751 infot = 1
752 CALL cptsv( -1, 0, r, a( 1, 1 ), b, 1, info )
753 CALL chkxer( 'CPTSV ', infot, nout, lerr, ok )
754 infot = 2
755 CALL cptsv( 0, -1, r, a( 1, 1 ), b, 1, info )
756 CALL chkxer( 'CPTSV ', infot, nout, lerr, ok )
757 infot = 6
758 CALL cptsv( 2, 0, r, a( 1, 1 ), b, 1, info )
759 CALL chkxer( 'CPTSV ', infot, nout, lerr, ok )
760*
761* CPTSVX
762*
763 srnamt = 'CPTSVX'
764 infot = 1
765 CALL cptsvx( '/', 0, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
766 $ 1, rcond, r1, r2, w, rw, info )
767 CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
768 infot = 2
769 CALL cptsvx( 'N', -1, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
770 $ 1, rcond, r1, r2, w, rw, info )
771 CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
772 infot = 3
773 CALL cptsvx( 'N', 0, -1, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
774 $ 1, rcond, r1, r2, w, rw, info )
775 CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
776 infot = 9
777 CALL cptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 1, x,
778 $ 2, rcond, r1, r2, w, rw, info )
779 CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
780 infot = 11
781 CALL cptsvx( 'N', 2, 0, r, a( 1, 1 ), rf, af( 1, 1 ), b, 2, x,
782 $ 1, rcond, r1, r2, w, rw, info )
783 CALL chkxer( 'CPTSVX', infot, nout, lerr, ok )
784*
785 ELSE IF( lsamen( 2, c2, 'HE' ) ) THEN
786*
787* CHESV
788*
789 srnamt = 'CHESV '
790 infot = 1
791 CALL chesv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
792 CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
793 infot = 2
794 CALL chesv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
795 CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
796 infot = 3
797 CALL chesv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
798 CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
799 infot = 5
800 CALL chesv( 'U', 2, 0, a, 1, ip, b, 2, w, 1, info )
801 CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
802 infot = 8
803 CALL chesv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
804 CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
805 infot = 10
806 CALL chesv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
807 CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
808 infot = 10
809 CALL chesv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
810 CALL chkxer( 'CHESV ', infot, nout, lerr, ok )
811*
812* CHESVX
813*
814 srnamt = 'CHESVX'
815 infot = 1
816 CALL chesvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
817 $ rcond, r1, r2, w, 1, rw, info )
818 CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
819 infot = 2
820 CALL chesvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
821 $ rcond, r1, r2, w, 1, rw, info )
822 CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
823 infot = 3
824 CALL chesvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
825 $ rcond, r1, r2, w, 1, rw, info )
826 CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
827 infot = 4
828 CALL chesvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
829 $ rcond, r1, r2, w, 1, rw, info )
830 CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
831 infot = 6
832 CALL chesvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
833 $ rcond, r1, r2, w, 4, rw, info )
834 CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
835 infot = 8
836 CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
837 $ rcond, r1, r2, w, 4, rw, info )
838 CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
839 infot = 11
840 CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
841 $ rcond, r1, r2, w, 4, rw, info )
842 CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
843 infot = 13
844 CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
845 $ rcond, r1, r2, w, 4, rw, info )
846 CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
847 infot = 18
848 CALL chesvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
849 $ rcond, r1, r2, w, 3, rw, info )
850 CALL chkxer( 'CHESVX', infot, nout, lerr, ok )
851*
852* CHESVXX
853*
854 n_err_bnds = 3
855 nparams = 1
856 srnamt = 'CHESVXX'
857 infot = 1
858 CALL chesvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
859 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
860 $ err_bnds_c, nparams, params, w, rw, info )
861 CALL chkxer( 'CHESVXX', infot, nout, lerr, ok )
862 infot = 2
863 CALL chesvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
864 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
865 $ err_bnds_c, nparams, params, w, rw, info )
866 CALL chkxer( 'CHESVXX', infot, nout, lerr, ok )
867 infot = 3
868 CALL chesvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
869 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
870 $ err_bnds_c, nparams, params, w, rw, info )
871 CALL chkxer( 'CHESVXX', infot, nout, lerr, ok )
872 infot = 4
873 CALL chesvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, c, b, 1, x,
874 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
875 $ err_bnds_c, nparams, params, w, rw, info )
876 CALL chkxer( 'CHESVXX', infot, nout, lerr, ok )
877 infot = 6
878 CALL chesvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, c, b, 2, x,
879 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
880 $ err_bnds_c, nparams, params, w, rw, info )
881 CALL chkxer( 'CHESVXX', infot, nout, lerr, ok )
882 infot = 8
883 CALL chesvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, c, b, 2, x,
884 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
885 $ err_bnds_c, nparams, params, w, rw, info )
886 CALL chkxer( 'CHESVXX', infot, nout, lerr, ok )
887 infot = 9
888 eq = '/'
889 CALL chesvxx( 'F', 'U', 0, 0, a, 1, af, 1, ip, eq, c, b, 1, x,
890 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
891 $ err_bnds_c, nparams, params, w, rw, info )
892 CALL chkxer( 'CHESVXX', infot, nout, lerr, ok )
893 infot = 10
894 eq = 'Y'
895 CALL chesvxx( 'F', '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( 'CHESVXX', infot, nout, lerr, ok )
899 infot = 12
900 CALL chesvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, c, b, 1, x,
901 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
902 $ err_bnds_c, nparams, params, w, rw, info )
903 CALL chkxer( 'CHESVXX', infot, nout, lerr, ok )
904 infot = 14
905 CALL chesvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, c, b, 2, x,
906 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
907 $ err_bnds_c, nparams, params, w, rw, info )
908 CALL chkxer( 'CHESVXX', infot, nout, lerr, ok )
909*
910 ELSE IF( lsamen( 2, c2, 'HR' ) ) THEN
911*
912* CHESV_ROOK
913*
914 srnamt = 'CHESV_ROOK'
915 infot = 1
916 CALL chesv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
917 CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
918 infot = 2
919 CALL chesv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
920 CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
921 infot = 3
922 CALL chesv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
923 CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
924 infot = 8
925 CALL chesv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
926 CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
927 infot = 10
928 CALL chesv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
929 CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
930 infot = 10
931 CALL chesv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
932 CALL chkxer( 'CHESV_ROOK', infot, nout, lerr, ok )
933*
934 ELSE IF( lsamen( 2, c2, 'HK' ) ) THEN
935*
936* CHESV_RK
937*
938* Test error exits of the driver that uses factorization
939* of a symmetric indefinite matrix with rook
940* (bounded Bunch-Kaufman) pivoting with the new storage
941* format for factors L ( or U) and D.
942*
943* L (or U) is stored in A, diagonal of D is stored on the
944* diagonal of A, subdiagonal of D is stored in a separate array E.
945*
946 srnamt = 'CHESV_RK'
947 infot = 1
948 CALL chesv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
949 CALL chkxer( 'CHESV_RK', infot, nout, lerr, ok )
950 infot = 2
951 CALL chesv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
952 CALL chkxer( 'CHESV_RK', infot, nout, lerr, ok )
953 infot = 3
954 CALL chesv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
955 CALL chkxer( 'CHESV_RK', infot, nout, lerr, ok )
956 infot = 5
957 CALL chesv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
958 CALL chkxer( 'CHESV_RK', infot, nout, lerr, ok )
959 infot = 9
960 CALL chesv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
961 CALL chkxer( 'CHESV_RK', infot, nout, lerr, ok )
962 infot = 11
963 CALL chesv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
964 CALL chkxer( 'CHESV_RK', infot, nout, lerr, ok )
965 infot = 11
966 CALL chesv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
967 CALL chkxer( 'CHESV_RK', infot, nout, lerr, ok )
968*
969 ELSE IF( lsamen( 2, c2, 'HP' ) ) THEN
970*
971* CHPSV
972*
973 srnamt = 'CHPSV '
974 infot = 1
975 CALL chpsv( '/', 0, 0, a, ip, b, 1, info )
976 CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
977 infot = 2
978 CALL chpsv( 'U', -1, 0, a, ip, b, 1, info )
979 CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
980 infot = 3
981 CALL chpsv( 'U', 0, -1, a, ip, b, 1, info )
982 CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
983 infot = 7
984 CALL chpsv( 'U', 2, 0, a, ip, b, 1, info )
985 CALL chkxer( 'CHPSV ', infot, nout, lerr, ok )
986*
987* CHPSVX
988*
989 srnamt = 'CHPSVX'
990 infot = 1
991 CALL chpsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
992 $ r2, w, rw, info )
993 CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
994 infot = 2
995 CALL chpsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
996 $ r2, w, rw, info )
997 CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
998 infot = 3
999 CALL chpsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1000 $ r2, w, rw, info )
1001 CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
1002 infot = 4
1003 CALL chpsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1004 $ r2, w, rw, info )
1005 CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
1006 infot = 9
1007 CALL chpsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1008 $ r2, w, rw, info )
1009 CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
1010 infot = 11
1011 CALL chpsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1012 $ r2, w, rw, info )
1013 CALL chkxer( 'CHPSVX', infot, nout, lerr, ok )
1014*
1015 ELSE IF( lsamen( 2, c2, 'SY' ) ) THEN
1016*
1017* CSYSV
1018*
1019 srnamt = 'CSYSV '
1020 infot = 1
1021 CALL csysv( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
1022 CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
1023 infot = 2
1024 CALL csysv( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
1025 CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
1026 infot = 3
1027 CALL csysv( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
1028 CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
1029 infot = 8
1030 CALL csysv( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
1031 CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
1032 infot = 10
1033 CALL csysv( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
1034 CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
1035 infot = 10
1036 CALL csysv( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
1037 CALL chkxer( 'CSYSV ', infot, nout, lerr, ok )
1038*
1039* CSYSVX
1040*
1041 srnamt = 'CSYSVX'
1042 infot = 1
1043 CALL csysvx( '/', 'U', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
1044 $ rcond, r1, r2, w, 1, rw, info )
1045 CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
1046 infot = 2
1047 CALL csysvx( 'N', '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1,
1048 $ rcond, r1, r2, w, 1, rw, info )
1049 CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
1050 infot = 3
1051 CALL csysvx( 'N', 'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1,
1052 $ rcond, r1, r2, w, 1, rw, info )
1053 CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
1054 infot = 4
1055 CALL csysvx( 'N', 'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1,
1056 $ rcond, r1, r2, w, 1, rw, info )
1057 CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
1058 infot = 6
1059 CALL csysvx( 'N', 'U', 2, 0, a, 1, af, 2, ip, b, 2, x, 2,
1060 $ rcond, r1, r2, w, 4, rw, info )
1061 CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
1062 infot = 8
1063 CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 1, ip, b, 2, x, 2,
1064 $ rcond, r1, r2, w, 4, rw, info )
1065 CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
1066 infot = 11
1067 CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 1, x, 2,
1068 $ rcond, r1, r2, w, 4, rw, info )
1069 CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
1070 infot = 13
1071 CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 1,
1072 $ rcond, r1, r2, w, 4, rw, info )
1073 CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
1074 infot = 18
1075 CALL csysvx( 'N', 'U', 2, 0, a, 2, af, 2, ip, b, 2, x, 2,
1076 $ rcond, r1, r2, w, 3, rw, info )
1077 CALL chkxer( 'CSYSVX', infot, nout, lerr, ok )
1078*
1079* CSYSVXX
1080*
1081 n_err_bnds = 3
1082 nparams = 1
1083 srnamt = 'CSYSVXX'
1084 infot = 1
1085 eq = 'N'
1086 CALL csysvxx( '/', 'U', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
1087 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1088 $ err_bnds_c, nparams, params, w, rw, info )
1089 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1090 infot = 2
1091 CALL csysvxx( 'N', '/', 0, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
1092 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1093 $ err_bnds_c, nparams, params, w, rw, info )
1094 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1095 infot = 3
1096 CALL csysvxx( 'N', 'U', -1, 0, a, 1, af, 1, ip, eq, r, b, 1, x,
1097 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1098 $ err_bnds_c, nparams, params, w, rw, info )
1099 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1100 infot = 4
1101 eq = '/'
1102 CALL csysvxx( 'N', 'U', 0, -1, a, 1, af, 1, ip, eq, r, b, 1, x,
1103 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1104 $ err_bnds_c, nparams, params, w, rw, info )
1105 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1106 eq = 'Y'
1107 infot = 6
1108 CALL csysvxx( 'N', 'U', 2, 0, a, 1, af, 2, ip, eq, r, b, 2, x,
1109 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1110 $ err_bnds_c, nparams, params, w, rw, info )
1111 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1112 infot = 8
1113 CALL csysvxx( 'N', 'U', 2, 0, a, 2, af, 1, ip, eq, r, b, 2, x,
1114 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1115 $ err_bnds_c, nparams, params, w, rw, info )
1116 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1117 infot = 10
1118 CALL csysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, 'A', r, b, 2, x,
1119 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1120 $ err_bnds_c, nparams, params, w, rw, info )
1121 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1122 infot = 11
1123 eq='Y'
1124 CALL csysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
1125 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1126 $ err_bnds_c, nparams, params, w, rw, info )
1127 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1128 infot = 11
1129 eq='Y'
1130 r(1) = -one
1131 CALL csysvxx( 'F', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
1132 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1133 $ err_bnds_c, nparams, params, w, rw, info )
1134 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1135 infot = 13
1136 eq = 'N'
1137 CALL csysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 1, x,
1138 $ 2, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1139 $ err_bnds_c, nparams, params, w, rw, info )
1140 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1141 infot = 15
1142 CALL csysvxx( 'N', 'U', 2, 0, a, 2, af, 2, ip, eq, r, b, 2, x,
1143 $ 1, rcond, rpvgrw, berr, n_err_bnds, err_bnds_n,
1144 $ err_bnds_c, nparams, params, w, rw, info )
1145 CALL chkxer( 'CSYSVXX', infot, nout, lerr, ok )
1146*
1147 ELSE IF( lsamen( 2, c2, 'SR' ) ) THEN
1148*
1149* CSYSV_ROOK
1150*
1151 srnamt = 'CSYSV_ROOK'
1152 infot = 1
1153 CALL csysv_rook( '/', 0, 0, a, 1, ip, b, 1, w, 1, info )
1154 CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
1155 infot = 2
1156 CALL csysv_rook( 'U', -1, 0, a, 1, ip, b, 1, w, 1, info )
1157 CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
1158 infot = 3
1159 CALL csysv_rook( 'U', 0, -1, a, 1, ip, b, 1, w, 1, info )
1160 CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
1161 infot = 8
1162 CALL csysv_rook( 'U', 2, 0, a, 2, ip, b, 1, w, 1, info )
1163 CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
1164 infot = 10
1165 CALL csysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, 0, info )
1166 CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
1167 infot = 10
1168 CALL csysv_rook( 'U', 0, 0, a, 1, ip, b, 1, w, -2, info )
1169 CALL chkxer( 'CSYSV_ROOK', infot, nout, lerr, ok )
1170*
1171 ELSE IF( lsamen( 2, c2, 'SK' ) ) THEN
1172*
1173* CSYSV_RK
1174*
1175* Test error exits of the driver that uses factorization
1176* of a symmetric indefinite matrix with rook
1177* (bounded Bunch-Kaufman) pivoting with the new storage
1178* format for factors L ( or U) and D.
1179*
1180* L (or U) is stored in A, diagonal of D is stored on the
1181* diagonal of A, subdiagonal of D is stored in a separate array E.
1182*
1183 srnamt = 'CSYSV_RK'
1184 infot = 1
1185 CALL csysv_rk( '/', 0, 0, a, 1, e, ip, b, 1, w, 1, info )
1186 CALL chkxer( 'CSYSV_RK', infot, nout, lerr, ok )
1187 infot = 2
1188 CALL csysv_rk( 'U', -1, 0, a, 1, e, ip, b, 1, w, 1, info )
1189 CALL chkxer( 'CSYSV_RK', infot, nout, lerr, ok )
1190 infot = 3
1191 CALL csysv_rk( 'U', 0, -1, a, 1, e, ip, b, 1, w, 1, info )
1192 CALL chkxer( 'CSYSV_RK', infot, nout, lerr, ok )
1193 infot = 5
1194 CALL csysv_rk( 'U', 2, 0, a, 1, e, ip, b, 2, w, 1, info )
1195 CALL chkxer( 'CSYSV_RK', infot, nout, lerr, ok )
1196 infot = 9
1197 CALL csysv_rk( 'U', 2, 0, a, 2, e, ip, b, 1, w, 1, info )
1198 CALL chkxer( 'CSYSV_RK', infot, nout, lerr, ok )
1199 infot = 11
1200 CALL csysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, 0, info )
1201 CALL chkxer( 'CSYSV_RK', infot, nout, lerr, ok )
1202 infot = 11
1203 CALL csysv_rk( 'U', 0, 0, a, 1, e, ip, b, 1, w, -2, info )
1204 CALL chkxer( 'CSYSV_RK', infot, nout, lerr, ok )
1205*
1206 ELSE IF( lsamen( 2, c2, 'SP' ) ) THEN
1207*
1208* CSPSV
1209*
1210 srnamt = 'CSPSV '
1211 infot = 1
1212 CALL cspsv( '/', 0, 0, a, ip, b, 1, info )
1213 CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
1214 infot = 2
1215 CALL cspsv( 'U', -1, 0, a, ip, b, 1, info )
1216 CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
1217 infot = 3
1218 CALL cspsv( 'U', 0, -1, a, ip, b, 1, info )
1219 CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
1220 infot = 7
1221 CALL cspsv( 'U', 2, 0, a, ip, b, 1, info )
1222 CALL chkxer( 'CSPSV ', infot, nout, lerr, ok )
1223*
1224* CSPSVX
1225*
1226 srnamt = 'CSPSVX'
1227 infot = 1
1228 CALL cspsvx( '/', 'U', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1229 $ r2, w, rw, info )
1230 CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
1231 infot = 2
1232 CALL cspsvx( 'N', '/', 0, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1233 $ r2, w, rw, info )
1234 CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
1235 infot = 3
1236 CALL cspsvx( 'N', 'U', -1, 0, a, af, ip, b, 1, x, 1, rcond, r1,
1237 $ r2, w, rw, info )
1238 CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
1239 infot = 4
1240 CALL cspsvx( 'N', 'U', 0, -1, a, af, ip, b, 1, x, 1, rcond, r1,
1241 $ r2, w, rw, info )
1242 CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
1243 infot = 9
1244 CALL cspsvx( 'N', 'U', 2, 0, a, af, ip, b, 1, x, 2, rcond, r1,
1245 $ r2, w, rw, info )
1246 CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
1247 infot = 11
1248 CALL cspsvx( 'N', 'U', 2, 0, a, af, ip, b, 2, x, 1, rcond, r1,
1249 $ r2, w, rw, info )
1250 CALL chkxer( 'CSPSVX', infot, nout, lerr, ok )
1251 END IF
1252*
1253* Print a summary line.
1254*
1255 IF( ok ) THEN
1256 WRITE( nout, fmt = 9999 )path
1257 ELSE
1258 WRITE( nout, fmt = 9998 )path
1259 END IF
1260*
1261 9999 FORMAT( 1x, a3, ' drivers passed the tests of the error exits' )
1262 9998 FORMAT( ' *** ', a3, ' drivers failed the tests of the error ',
1263 $ 'exits ***' )
1264*
1265 RETURN
1266*
1267* End of CERRVXX
1268*
1269 END
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3224
subroutine cerrvx(path, nunit)
CERRVX
Definition cerrvx.f:55
subroutine cgbsv(n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)
CGBSV computes the solution to system of linear equations A * X = B for GB matrices (simple driver)
Definition cgbsv.f:162
subroutine cgbsvx(fact, trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CGBSVX computes the solution to system of linear equations A * X = B for GB matrices
Definition cgbsvx.f:370
subroutine cgbsvxx(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)
CGBSVXX computes the solution to system of linear equations A * X = B for GB matrices
Definition cgbsvxx.f:563
subroutine cgesv(n, nrhs, a, lda, ipiv, b, ldb, info)
Download CGESV + dependencies <a href="http://www.netlib.org/cgi-bin/netlibfiles....
Definition cgesv.f:124
subroutine cgesvx(fact, trans, n, nrhs, a, lda, af, ldaf, ipiv, equed, r, c, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CGESVX computes the solution to system of linear equations A * X = B for GE matrices
Definition cgesvx.f:350
subroutine cgesvxx(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)
CGESVXX computes the solution to system of linear equations A * X = B for GE matrices
Definition cgesvxx.f:543
subroutine cgtsv(n, nrhs, dl, d, du, b, ldb, info)
CGTSV computes the solution to system of linear equations A * X = B for GT matrices
Definition cgtsv.f:124
subroutine cgtsvx(fact, trans, n, nrhs, dl, d, du, dlf, df, duf, du2, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CGTSVX computes the solution to system of linear equations A * X = B for GT matrices
Definition cgtsvx.f:294
subroutine chesv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)
CHESV_RK computes the solution to system of linear equations A * X = B for SY matrices
Definition chesv_rk.f:228
subroutine csysv_rk(uplo, n, nrhs, a, lda, e, ipiv, b, ldb, work, lwork, info)
CSYSV_RK computes the solution to system of linear equations A * X = B for SY matrices
Definition csysv_rk.f:228
subroutine chesv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
CHESV_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using the ...
Definition chesv_rook.f:205
subroutine csysv_rook(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
CSYSV_ROOK computes the solution to system of linear equations A * X = B for SY matrices
Definition csysv_rook.f:204
subroutine csysv(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
CSYSV computes the solution to system of linear equations A * X = B for SY matrices
Definition csysv.f:171
subroutine chesv(uplo, n, nrhs, a, lda, ipiv, b, ldb, work, lwork, info)
CHESV computes the solution to system of linear equations A * X = B for HE matrices
Definition chesv.f:171
subroutine chesvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, rwork, info)
CHESVX computes the solution to system of linear equations A * X = B for HE matrices
Definition chesvx.f:285
subroutine csysvx(fact, uplo, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, lwork, rwork, info)
CSYSVX computes the solution to system of linear equations A * X = B for SY matrices
Definition csysvx.f:285
subroutine csysvxx(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)
CSYSVXX computes the solution to system of linear equations A * X = B for SY matrices
Definition csysvxx.f:509
subroutine chesvxx(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)
CHESVXX computes the solution to system of linear equations A * X = B for HE matrices
Definition chesvxx.f:509
subroutine chpsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)
CHPSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition chpsv.f:162
subroutine cspsv(uplo, n, nrhs, ap, ipiv, b, ldb, info)
CSPSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition cspsv.f:162
subroutine cspsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CSPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition cspsvx.f:277
subroutine chpsvx(fact, uplo, n, nrhs, ap, afp, ipiv, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CHPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition chpsvx.f:277
subroutine cpbsv(uplo, n, kd, nrhs, ab, ldab, b, ldb, info)
CPBSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition cpbsv.f:164
subroutine cpbsvx(fact, uplo, n, kd, nrhs, ab, ldab, afb, ldafb, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CPBSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition cpbsvx.f:342
subroutine cposv(uplo, n, nrhs, a, lda, b, ldb, info)
CPOSV computes the solution to system of linear equations A * X = B for PO matrices
Definition cposv.f:130
subroutine cposvx(fact, uplo, n, nrhs, a, lda, af, ldaf, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CPOSVX computes the solution to system of linear equations A * X = B for PO matrices
Definition cposvx.f:306
subroutine cposvxx(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)
CPOSVXX computes the solution to system of linear equations A * X = B for PO matrices
Definition cposvxx.f:496
subroutine cppsv(uplo, n, nrhs, ap, b, ldb, info)
CPPSV computes the solution to system of linear equations A * X = B for OTHER matrices
Definition cppsv.f:144
subroutine cppsvx(fact, uplo, n, nrhs, ap, afp, equed, s, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CPPSVX computes the solution to system of linear equations A * X = B for OTHER matrices
Definition cppsvx.f:311
subroutine cptsv(n, nrhs, d, e, b, ldb, info)
CPTSV computes the solution to system of linear equations A * X = B for PT matrices
Definition cptsv.f:115
subroutine cptsvx(fact, n, nrhs, d, e, df, ef, b, ldb, x, ldx, rcond, ferr, berr, work, rwork, info)
CPTSVX computes the solution to system of linear equations A * X = B for PT matrices
Definition cptsvx.f:234