OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
cerrgex.f
Go to the documentation of this file.
1*> \brief \b CERRGEX
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 CERRGE( 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*> CERRGE tests the error exits for the COMPLEX routines
25*> for general matrices.
26*>
27*> Note that this file is used only when the XBLAS are available,
28*> otherwise cerrge.f defines this subroutine.
29*> \endverbatim
30*
31* Arguments:
32* ==========
33*
34*> \param[in] PATH
35*> \verbatim
36*> PATH is CHARACTER*3
37*> The LAPACK path name for the routines to be tested.
38*> \endverbatim
39*>
40*> \param[in] NUNIT
41*> \verbatim
42*> NUNIT is INTEGER
43*> The unit number for output.
44*> \endverbatim
45*
46* Authors:
47* ========
48*
49*> \author Univ. of Tennessee
50*> \author Univ. of California Berkeley
51*> \author Univ. of Colorado Denver
52*> \author NAG Ltd.
53*
54*> \ingroup complex_lin
55*
56* =====================================================================
57 SUBROUTINE cerrge( PATH, NUNIT )
58*
59* -- LAPACK test routine --
60* -- LAPACK is a software package provided by Univ. of Tennessee, --
61* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
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 ANRM, CCOND, RCOND, BERR
79* ..
80* .. Local Arrays ..
81 INTEGER IP( NMAX )
82 REAL R( NMAX ), R1( NMAX ), R2( NMAX ), CS( NMAX ),
83 $ RS( NMAX )
84 COMPLEX A( NMAX, NMAX ), AF( NMAX, NMAX ), B( NMAX ),
85 $ W( 2*NMAX ), X( NMAX ), ERR_BNDS_N( NMAX, 3 ),
86 $ ERR_BNDS_C( NMAX, 3 ), PARAMS( 1 )
87* ..
88* .. External Functions ..
89 LOGICAL LSAMEN
90 EXTERNAL lsamen
91* ..
92* .. External Subroutines ..
93 EXTERNAL alaesm, cgbcon, cgbequ, cgbrfs, cgbtf2, cgbtrf,
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 cs( j ) = 0.
129 rs( j ) = 0.
130 ip( j ) = j
131 20 CONTINUE
132 ok = .true.
133*
134* Test error exits of the routines that use the LU decomposition
135* of a general matrix.
136*
137 IF( lsamen( 2, c2, 'GE' ) ) THEN
138*
139* CGETRF
140*
141 srnamt = 'CGETRF'
142 infot = 1
143 CALL cgetrf( -1, 0, a, 1, ip, info )
144 CALL chkxer( 'CGETRF', infot, nout, lerr, ok )
145 infot = 2
146 CALL cgetrf( 0, -1, a, 1, ip, info )
147 CALL chkxer( 'CGETRF', infot, nout, lerr, ok )
148 infot = 4
149 CALL cgetrf( 2, 1, a, 1, ip, info )
150 CALL chkxer( 'CGETRF', infot, nout, lerr, ok )
151*
152* CGETF2
153*
154 srnamt = 'CGETF2'
155 infot = 1
156 CALL cgetf2( -1, 0, a, 1, ip, info )
157 CALL chkxer( 'CGETF2', infot, nout, lerr, ok )
158 infot = 2
159 CALL cgetf2( 0, -1, a, 1, ip, info )
160 CALL chkxer( 'CGETF2', infot, nout, lerr, ok )
161 infot = 4
162 CALL cgetf2( 2, 1, a, 1, ip, info )
163 CALL chkxer( 'CGETF2', infot, nout, lerr, ok )
164*
165* CGETRI
166*
167 srnamt = 'CGETRI'
168 infot = 1
169 CALL cgetri( -1, a, 1, ip, w, 1, info )
170 CALL chkxer( 'CGETRI', infot, nout, lerr, ok )
171 infot = 3
172 CALL cgetri( 2, a, 1, ip, w, 2, info )
173 CALL chkxer( 'CGETRI', infot, nout, lerr, ok )
174 infot = 6
175 CALL cgetri( 2, a, 2, ip, w, 1, info )
176 CALL chkxer( 'CGETRI', infot, nout, lerr, ok )
177*
178* CGETRS
179*
180 srnamt = 'CGETRS'
181 infot = 1
182 CALL cgetrs( '/', 0, 0, a, 1, ip, b, 1, info )
183 CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
184 infot = 2
185 CALL cgetrs( 'N', -1, 0, a, 1, ip, b, 1, info )
186 CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
187 infot = 3
188 CALL cgetrs( 'N', 0, -1, a, 1, ip, b, 1, info )
189 CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
190 infot = 5
191 CALL cgetrs( 'N', 2, 1, a, 1, ip, b, 2, info )
192 CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
193 infot = 8
194 CALL cgetrs( 'N', 2, 1, a, 2, ip, b, 1, info )
195 CALL chkxer( 'CGETRS', infot, nout, lerr, ok )
196*
197* CGERFS
198*
199 srnamt = 'cgerfs'
200 INFOT = 1
201 CALL CGERFS( '/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
202 $ r, info )
203 CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
204 infot = 2
205 CALL cgerfs( 'N', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
206 $ w, r, info )
207 CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
208 infot = 3
209 CALL cgerfs( 'N', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
210 $ w, r, info )
211 CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
212 infot = 5
213 CALL cgerfs( 'N', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
214 $ r, info )
215 CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
216 infot = 7
217 CALL cgerfs( 'N', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
218 $ r, info )
219 CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
220 infot = 10
221 CALL cgerfs( 'N', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
222 $ r, info )
223 CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
224 infot = 12
225 CALL cgerfs( 'N', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
226 $ r, info )
227 CALL chkxer( 'CGERFS', infot, nout, lerr, ok )
228*
229* CGERFSX
230*
231 n_err_bnds = 3
232 nparams = 0
233 srnamt = 'CGERFSX'
234 infot = 1
235 CALL cgerfsx( '/', eq, 0, 0, a, 1, af, 1, ip, rs, cs, b, 1, x,
236 $ 1, rcond, berr, n_err_bnds, err_bnds_n,
237 $ err_bnds_c, nparams, params, w, r, info )
238 CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
239 infot = 2
240 eq = '/'
241 CALL cgerfsx( 'N', eq, 2, 1, a, 1, af, 2, ip, rs, cs, b, 2, x,
242 $ 2, rcond, berr, n_err_bnds, err_bnds_n,
243 $ err_bnds_c, nparams, params, w, r, info )
244 CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
245 infot = 3
246 eq = 'R'
247 CALL cgerfsx( 'N', eq, -1, 0, a, 1, af, 1, ip, rs, cs, b, 1, x,
248 $ 1, rcond, berr, n_err_bnds, err_bnds_n,
249 $ err_bnds_c, nparams, params, w, r, info )
250 CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
251 infot = 4
252 CALL cgerfsx( 'N', eq, 0, -1, a, 1, af, 1, ip, rs, cs, b, 1, x,
253 $ 1, rcond, berr, n_err_bnds, err_bnds_n,
254 $ err_bnds_c, nparams, params, w, r, info )
255 CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
256 infot = 6
257 CALL cgerfsx( 'N', eq, 2, 1, a, 1, af, 2, ip, rs, cs, b, 2, x,
258 $ 2, rcond, berr, n_err_bnds, err_bnds_n,
259 $ err_bnds_c, nparams, params, w, r, info )
260 CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
261 infot = 8
262 CALL cgerfsx( 'N', eq, 2, 1, a, 2, af, 1, ip, rs, cs, b, 2, x,
263 $ 2, rcond, berr, n_err_bnds, err_bnds_n,
264 $ err_bnds_c, nparams, params, w, r, info )
265 CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
266 infot = 13
267 eq = 'C'
268 CALL cgerfsx( 'N', eq, 2, 1, a, 2, af, 2, ip, rs, cs, b, 1, x,
269 $ 2, rcond, berr, n_err_bnds, err_bnds_n,
270 $ err_bnds_c, nparams, params, w, r, info )
271 CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
272 infot = 15
273 CALL cgerfsx( 'N', eq, 2, 1, a, 2, af, 2, ip, rs, cs, b, 2, x,
274 $ 1, rcond, berr, n_err_bnds, err_bnds_n,
275 $ err_bnds_c, nparams, params, w, r, info )
276 CALL chkxer( 'CGERFSX', infot, nout, lerr, ok )
277*
278* CGECON
279*
280 srnamt = 'CGECON'
281 infot = 1
282 CALL cgecon( '/', 0, a, 1, anrm, rcond, w, r, info )
283 CALL chkxer( 'CGECON', infot, nout, lerr, ok )
284 infot = 2
285 CALL cgecon( '1', -1, a, 1, anrm, rcond, w, r, info )
286 CALL chkxer( 'CGECON', infot, nout, lerr, ok )
287 infot = 4
288 CALL cgecon( '1', 2, a, 1, anrm, rcond, w, r, info )
289 CALL chkxer( 'cgecon', INFOT, NOUT, LERR, OK )
290*
291* CGEEQU
292*
293 SRNAMT = 'cgeequ'
294 INFOT = 1
295 CALL CGEEQU( -1, 0, A, 1, R1, R2, RCOND, CCOND, ANRM, INFO )
296 CALL CHKXER( 'cgeequ', INFOT, NOUT, LERR, OK )
297 INFOT = 2
298 CALL CGEEQU( 0, -1, A, 1, R1, R2, RCOND, CCOND, ANRM, INFO )
299 CALL CHKXER( 'cgeequ', INFOT, NOUT, LERR, OK )
300 INFOT = 4
301 CALL CGEEQU( 2, 2, A, 1, R1, R2, RCOND, CCOND, ANRM, INFO )
302 CALL CHKXER( 'cgeequ', INFOT, NOUT, LERR, OK )
303*
304* CGEEQUB
305*
306 SRNAMT = 'cgeequb'
307 INFOT = 1
308 CALL CGEEQUB( -1, 0, A, 1, R1, R2, RCOND, CCOND, ANRM, INFO )
309 CALL CHKXER( 'cgeequb', INFOT, NOUT, LERR, OK )
310 INFOT = 2
311 CALL CGEEQUB( 0, -1, A, 1, R1, R2, RCOND, CCOND, ANRM, INFO )
312 CALL CHKXER( 'cgeequb', INFOT, NOUT, LERR, OK )
313 INFOT = 4
314 CALL CGEEQUB( 2, 2, A, 1, R1, R2, RCOND, CCOND, ANRM, INFO )
315 CALL CHKXER( 'cgeequb', INFOT, NOUT, LERR, OK )
316*
317* Test error exits of the routines that use the LU decomposition
318* of a general band matrix.
319*
320 ELSE IF( LSAMEN( 2, C2, 'gb' ) ) THEN
321*
322* CGBTRF
323*
324 SRNAMT = 'cgbtrf'
325 INFOT = 1
326 CALL CGBTRF( -1, 0, 0, 0, A, 1, IP, INFO )
327 CALL CHKXER( 'cgbtrf', INFOT, NOUT, LERR, OK )
328 INFOT = 2
329 CALL CGBTRF( 0, -1, 0, 0, A, 1, IP, INFO )
330 CALL CHKXER( 'cgbtrf', INFOT, NOUT, LERR, OK )
331 INFOT = 3
332 CALL CGBTRF( 1, 1, -1, 0, A, 1, IP, INFO )
333 CALL CHKXER( 'cgbtrf', INFOT, NOUT, LERR, OK )
334 INFOT = 4
335 CALL CGBTRF( 1, 1, 0, -1, A, 1, IP, INFO )
336 CALL CHKXER( 'cgbtrf', INFOT, NOUT, LERR, OK )
337 INFOT = 6
338 CALL CGBTRF( 2, 2, 1, 1, A, 3, IP, INFO )
339 CALL CHKXER( 'cgbtrf', INFOT, NOUT, LERR, OK )
340*
341* CGBTF2
342*
343 SRNAMT = 'cgbtf2'
344 INFOT = 1
345 CALL CGBTF2( -1, 0, 0, 0, A, 1, IP, INFO )
346 CALL CHKXER( 'cgbtf2', INFOT, NOUT, LERR, OK )
347 INFOT = 2
348 CALL CGBTF2( 0, -1, 0, 0, A, 1, IP, INFO )
349 CALL CHKXER( 'cgbtf2', INFOT, NOUT, LERR, OK )
350 INFOT = 3
351 CALL CGBTF2( 1, 1, -1, 0, A, 1, IP, INFO )
352 CALL CHKXER( 'cgbtf2', INFOT, NOUT, LERR, OK )
353 INFOT = 4
354 CALL CGBTF2( 1, 1, 0, -1, A, 1, IP, INFO )
355 CALL CHKXER( 'cgbtf2', INFOT, NOUT, LERR, OK )
356 INFOT = 6
357 CALL CGBTF2( 2, 2, 1, 1, A, 3, IP, INFO )
358 CALL CHKXER( 'cgbtf2', INFOT, NOUT, LERR, OK )
359*
360* CGBTRS
361*
362 SRNAMT = 'cgbtrs'
363 INFOT = 1
364 CALL CGBTRS( '/', 0, 0, 0, 1, A, 1, IP, B, 1, INFO )
365 CALL CHKXER( 'cgbtrs', INFOT, NOUT, LERR, OK )
366 INFOT = 2
367 CALL CGBTRS( 'n', -1, 0, 0, 1, A, 1, IP, B, 1, INFO )
368 CALL CHKXER( 'cgbtrs', INFOT, NOUT, LERR, OK )
369 INFOT = 3
370 CALL CGBTRS( 'n', 1, -1, 0, 1, A, 1, IP, B, 1, INFO )
371 CALL CHKXER( 'cgbtrs', INFOT, NOUT, LERR, OK )
372 INFOT = 4
373 CALL CGBTRS( 'n', 1, 0, -1, 1, A, 1, IP, B, 1, INFO )
374 CALL CHKXER( 'cgbtrs', infot, nout, lerr, ok )
375 infot = 5
376 CALL cgbtrs( 'N', 1, 0, 0, -1, a, 1, ip, b, 1, info )
377 CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
378 infot = 7
379 CALL cgbtrs( 'N', 2, 1, 1, 1, a, 3, ip, b, 2, info )
380 CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
381 infot = 10
382 CALL cgbtrs( 'N', 2, 0, 0, 1, a, 1, ip, b, 1, info )
383 CALL chkxer( 'CGBTRS', infot, nout, lerr, ok )
384*
385* CGBRFS
386*
387 srnamt = 'CGBRFS'
388 infot = 1
389 CALL cgbrfs( '/', 0, 0, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
390 $ r2, w, r, info )
391 CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
392 infot = 2
393 CALL cgbrfs( 'N', -1, 0, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
394 $ r2, w, r, info )
395 CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
396 infot = 3
397 CALL cgbrfs( 'N', 1, -1, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
398 $ r2, w, r, info )
399 CALL chkxer( 'CGBRFS', infot, nout, lerr, ok )
400 infot = 4
401 CALL cgbrfs( 'n', 1, 0, -1, 0, A, 1, AF, 1, IP, B, 1, X, 1, R1,
402 $ R2, W, R, INFO )
403 CALL CHKXER( 'cgbrfs', INFOT, NOUT, LERR, OK )
404 INFOT = 5
405 CALL CGBRFS( 'n', 1, 0, 0, -1, A, 1, AF, 1, IP, B, 1, X, 1, R1,
406 $ R2, W, R, INFO )
407 CALL CHKXER( 'cgbrfs', INFOT, NOUT, LERR, OK )
408 INFOT = 7
409 CALL CGBRFS( 'n', 2, 1, 1, 1, A, 2, AF, 4, IP, B, 2, X, 2, R1,
410 $ R2, W, R, INFO )
411 CALL CHKXER( 'cgbrfs', INFOT, NOUT, LERR, OK )
412 INFOT = 9
413 CALL CGBRFS( 'n', 2, 1, 1, 1, A, 3, AF, 3, IP, B, 2, X, 2, R1,
414 $ R2, W, R, INFO )
415 CALL CHKXER( 'cgbrfs', INFOT, NOUT, LERR, OK )
416 INFOT = 12
417 CALL CGBRFS( 'n', 2, 0, 0, 1, A, 1, AF, 1, IP, B, 1, X, 2, R1,
418 $ R2, W, R, INFO )
419 CALL CHKXER( 'cgbrfs', INFOT, NOUT, LERR, OK )
420 INFOT = 14
421 CALL CGBRFS( 'n', 2, 0, 0, 1, A, 1, AF, 1, IP, B, 2, X, 1, R1,
422 $ R2, W, R, INFO )
423 CALL CHKXER( 'cgbrfs', INFOT, NOUT, LERR, OK )
424*
425* CGBRFSX
426*
427 N_ERR_BNDS = 3
428 NPARAMS = 0
429 SRNAMT = 'cgbrfsx'
430 INFOT = 1
431 CALL CGBRFSX( '/', EQ, 0, 0, 0, 0, A, 1, AF, 1, IP, RS, CS, B,
432 $ 1, X, 1, RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N,
433 $ ERR_BNDS_C, NPARAMS, PARAMS, W, R, INFO )
434 CALL CHKXER( 'cgbrfsx', INFOT, NOUT, LERR, OK )
435 INFOT = 2
436 EQ = '/'
437 CALL CGBRFSX( 'n', EQ, 2, 1, 1, 1, A, 1, AF, 2, IP, RS, CS, B,
438 $ 2, X, 2, RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N,
439 $ ERR_BNDS_C, NPARAMS, PARAMS, W, R, INFO )
440 CALL CHKXER( 'cgbrfsx', INFOT, NOUT, LERR, OK )
441 INFOT = 3
442 EQ = 'r'
443 CALL CGBRFSX( 'n', EQ, -1, 1, 1, 0, A, 1, AF, 1, IP, RS, CS, B,
444 $ 1, X, 1, RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N,
445 $ ERR_BNDS_C, NPARAMS, PARAMS, W, R, INFO )
446 CALL CHKXER( 'cgbrfsx', INFOT, NOUT, LERR, OK )
447 INFOT = 4
448 EQ = 'r'
449 CALL CGBRFSX( 'n', EQ, 2, -1, 1, 1, A, 3, AF, 4, IP, RS, CS, B,
450 $ 1, X, 1, RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N,
451 $ ERR_BNDS_C, NPARAMS, PARAMS, W, R, INFO )
452 CALL CHKXER( 'cgbrfsx', INFOT, NOUT, LERR, OK )
453 INFOT = 5
454 EQ = 'r'
455 CALL CGBRFSX( 'n', EQ, 2, 1, -1, 1, A, 3, AF, 4, IP, RS, CS, B,
456 $ 1, X, 1, RCOND, BERR, N_ERR_BNDS, ERR_BNDS_N,
457 $ ERR_BNDS_C, NPARAMS, PARAMS, W, R, INFO )
458 CALL CHKXER( 'cgbrfsx', infot, nout, lerr, ok )
459 infot = 6
460 CALL cgbrfsx( 'N', eq, 0, 0, 0, -1, a, 1, af, 1, ip, rs, cs, b,
461 $ 1, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
462 $ err_bnds_c, nparams, params, w, r, info )
463 CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
464 infot = 8
465 CALL cgbrfsx( 'N', eq, 2, 1, 1, 1, a, 1, af, 2, ip, rs, cs, b,
466 $ 2, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
467 $ err_bnds_c, nparams, params, w, r, info )
468 CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
469 infot = 10
470 CALL cgbrfsx( 'N', eq, 2, 1, 1, 1, a, 3, af, 3, ip, rs, cs, b,
471 $ 2, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
472 $ err_bnds_c, nparams, params, w, r, info )
473 CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
474 infot = 13
475 eq = 'C'
476 CALL cgbrfsx( 'N', eq, 2, 1, 1, 1, a, 3, af, 5, ip, rs, cs, b,
477 $ 1, x, 2, rcond, berr, n_err_bnds, err_bnds_n,
478 $ err_bnds_c, nparams, params, w, r, info )
479 CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
480 infot = 15
481 CALL cgbrfsx( 'N', eq, 2, 1, 1, 1, a, 3, af, 5, ip, rs, cs, b,
482 $ 2, x, 1, rcond, berr, n_err_bnds, err_bnds_n,
483 $ err_bnds_c, nparams, params, w, r, info )
484 CALL chkxer( 'CGBRFSX', infot, nout, lerr, ok )
485*
486* CGBCON
487*
488 srnamt = 'CGBCON'
489 infot = 1
490 CALL cgbcon( '/', 0, 0, 0, a, 1, ip, anrm, rcond, w, r, info )
491 CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
492 infot = 2
493 CALL cgbcon( '1', -1, 0, 0, a, 1, ip, anrm, rcond, w, r, info )
494 CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
495 infot = 3
496 CALL cgbcon( '1', 1, -1, 0, a, 1, ip, anrm, rcond, w, r, info )
497 CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
498 infot = 4
499 CALL cgbcon( '1', 1, 0, -1, a, 1, ip, anrm, rcond, w, r, info )
500 CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
501 infot = 6
502 CALL cgbcon( '1', 2, 1, 1, a, 3, ip, anrm, rcond, w, r, info )
503 CALL chkxer( 'CGBCON', infot, nout, lerr, ok )
504*
505* CGBEQU
506*
507 srnamt = 'CGBEQU'
508 infot = 1
509 CALL cgbequ( -1, 0, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
510 $ info )
511 CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
512 infot = 2
513 CALL cgbequ( 0, -1, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
514 $ info )
515 CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
516 infot = 3
517 CALL cgbequ( 1, 1, -1, 0, a, 1, r1, r2, rcond, ccond, anrm,
518 $ info )
519 CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
520 infot = 4
521 CALL cgbequ( 1, 1, 0, -1, a, 1, r1, r2, rcond, ccond, anrm,
522 $ info )
523 CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
524 infot = 6
525 CALL cgbequ( 2, 2, 1, 1, a, 2, r1, r2, rcond, ccond, anrm,
526 $ info )
527 CALL chkxer( 'CGBEQU', infot, nout, lerr, ok )
528*
529* CGBEQUB
530*
531 srnamt = 'CGBEQUB'
532 infot = 1
533 CALL cgbequb( -1, 0, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
534 $ info )
535 CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
536 infot = 2
537 CALL cgbequb( 0, -1, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
538 $ info )
539 CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
540 infot = 3
541 CALL cgbequb( 1, 1, -1, 0, a, 1, r1, r2, rcond, ccond, anrm,
542 $ info )
543 CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
544 infot = 4
545 CALL cgbequb( 1, 1, 0, -1, a, 1, r1, r2, rcond, ccond, anrm,
546 $ info )
547 CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
548 infot = 6
549 CALL cgbequb( 2, 2, 1, 1, a, 2, r1, r2, rcond, ccond, anrm,
550 $ info )
551 CALL chkxer( 'CGBEQUB', infot, nout, lerr, ok )
552 END IF
553*
554* Print a summary line.
555*
556 CALL alaesm( path, ok, nout )
557*
558 RETURN
559*
560* End of CERRGEX
561*
562 END
float cmplx[2]
Definition pblas.h:136
subroutine chkxer(srnamt, infot, nout, lerr, ok)
Definition cblat2.f:3196
subroutine alaesm(path, ok, nout)
ALAESM
Definition alaesm.f:63
subroutine cgbequ(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)
CGBEQU
Definition cgbequ.f:154
subroutine cgbequb(m, n, kl, ku, ab, ldab, r, c, rowcnd, colcnd, amax, info)
CGBEQUB
Definition cgbequb.f:161
subroutine cgbrfs(trans, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CGBRFS
Definition cgbrfs.f:206
subroutine cgbrfsx(trans, equed, n, kl, ku, nrhs, ab, ldab, afb, ldafb, ipiv, r, c, b, ldb, x, ldx, rcond, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, rwork, info)
CGBRFSX
Definition cgbrfsx.f:440
subroutine cgbtrf(m, n, kl, ku, ab, ldab, ipiv, info)
CGBTRF
Definition cgbtrf.f:144
subroutine cgbcon(norm, n, kl, ku, ab, ldab, ipiv, anorm, rcond, work, rwork, info)
CGBCON
Definition cgbcon.f:147
subroutine cgbtrs(trans, n, kl, ku, nrhs, ab, ldab, ipiv, b, ldb, info)
CGBTRS
Definition cgbtrs.f:138
subroutine cgbtf2(m, n, kl, ku, ab, ldab, ipiv, info)
CGBTF2 computes the LU factorization of a general band matrix using the unblocked version of the algo...
Definition cgbtf2.f:145
subroutine cgetrs(trans, n, nrhs, a, lda, ipiv, b, ldb, info)
CGETRS
Definition cgetrs.f:121
subroutine cgetrf(m, n, a, lda, ipiv, info)
CGETRF
Definition cgetrf.f:108
subroutine cgeequb(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)
CGEEQUB
Definition cgeequb.f:147
subroutine cgetf2(m, n, a, lda, ipiv, info)
CGETF2 computes the LU factorization of a general m-by-n matrix using partial pivoting with row inter...
Definition cgetf2.f:108
subroutine cgeequ(m, n, a, lda, r, c, rowcnd, colcnd, amax, info)
CGEEQU
Definition cgeequ.f:140
subroutine cgetri(n, a, lda, ipiv, work, lwork, info)
CGETRI
Definition cgetri.f:114
subroutine cgecon(norm, n, a, lda, anorm, rcond, work, rwork, info)
CGECON
Definition cgecon.f:124
subroutine cgerfs(trans, n, nrhs, a, lda, af, ldaf, ipiv, b, ldb, x, ldx, ferr, berr, work, rwork, info)
CGERFS
Definition cgerfs.f:186
subroutine cgerfsx(trans, equed, n, nrhs, a, lda, af, ldaf, ipiv, r, c, b, ldb, x, ldx, rcond, berr, n_err_bnds, err_bnds_norm, err_bnds_comp, nparams, params, work, rwork, info)
CGERFSX
Definition cgerfsx.f:414
subroutine cerrge(path, nunit)
CERRGE
Definition cerrge.f:55