56 SUBROUTINE cerrge( PATH, NUNIT )
72 parameter ( nmax = 4 )
77 REAL ANRM, CCOND, RCOND
81 REAL R( nmax ), R1( nmax ), R2( nmax )
82 COMPLEX A( nmax, nmax ), AF( nmax, nmax ), B( nmax ),
83 $ w( 2*nmax ), x( nmax )
100 COMMON / infoc / infot, nout, ok, lerr
101 COMMON / srnamc / srnamt
104 INTRINSIC cmplx, real
109 WRITE( nout, fmt = * )
116 a( i, j ) = cmplx( 1. /
REAL( I+J ), -1. /
REAL( I+J ) )
117 af( i, j ) = cmplx( 1. /
REAL( I+J ), -1. /
REAL( I+J ) )
131 IF( lsamen( 2, c2,
'GE' ) )
THEN
137 CALL cgetrf( -1, 0, a, 1, ip, info )
138 CALL chkxer(
'CGETRF', infot, nout, lerr, ok )
140 CALL cgetrf( 0, -1, a, 1, ip, info )
141 CALL chkxer(
'CGETRF', infot, nout, lerr, ok )
143 CALL cgetrf( 2, 1, a, 1, ip, info )
144 CALL chkxer(
'CGETRF', infot, nout, lerr, ok )
150 CALL cgetf2( -1, 0, a, 1, ip, info )
151 CALL chkxer(
'CGETF2', infot, nout, lerr, ok )
153 CALL cgetf2( 0, -1, a, 1, ip, info )
154 CALL chkxer(
'CGETF2', infot, nout, lerr, ok )
156 CALL cgetf2( 2, 1, a, 1, ip, info )
157 CALL chkxer(
'CGETF2', infot, nout, lerr, ok )
163 CALL cgetri( -1, a, 1, ip, w, 1, info )
164 CALL chkxer(
'CGETRI', infot, nout, lerr, ok )
166 CALL cgetri( 2, a, 1, ip, w, 2, info )
167 CALL chkxer(
'CGETRI', infot, nout, lerr, ok )
169 CALL cgetri( 2, a, 2, ip, w, 1, info )
170 CALL chkxer(
'CGETRI', infot, nout, lerr, ok )
176 CALL cgetrs(
'/', 0, 0, a, 1, ip, b, 1, info )
177 CALL chkxer(
'CGETRS', infot, nout, lerr, ok )
179 CALL cgetrs(
'N', -1, 0, a, 1, ip, b, 1, info )
180 CALL chkxer(
'CGETRS', infot, nout, lerr, ok )
182 CALL cgetrs(
'N', 0, -1, a, 1, ip, b, 1, info )
183 CALL chkxer(
'CGETRS', infot, nout, lerr, ok )
185 CALL cgetrs(
'N', 2, 1, a, 1, ip, b, 2, info )
186 CALL chkxer(
'CGETRS', infot, nout, lerr, ok )
188 CALL cgetrs(
'N', 2, 1, a, 2, ip, b, 1, info )
189 CALL chkxer(
'CGETRS', infot, nout, lerr, ok )
195 CALL cgerfs(
'/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
197 CALL chkxer(
'CGERFS', infot, nout, lerr, ok )
199 CALL cgerfs(
'N', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
201 CALL chkxer(
'CGERFS', infot, nout, lerr, ok )
203 CALL cgerfs(
'N', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
205 CALL chkxer(
'CGERFS', infot, nout, lerr, ok )
207 CALL cgerfs(
'N', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
209 CALL chkxer(
'CGERFS', infot, nout, lerr, ok )
211 CALL cgerfs(
'N', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
213 CALL chkxer(
'CGERFS', infot, nout, lerr, ok )
215 CALL cgerfs(
'N', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
217 CALL chkxer(
'CGERFS', infot, nout, lerr, ok )
219 CALL cgerfs(
'N', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
221 CALL chkxer(
'CGERFS', infot, nout, lerr, ok )
227 CALL cgecon(
'/', 0, a, 1, anrm, rcond, w, r, info )
228 CALL chkxer(
'CGECON', infot, nout, lerr, ok )
230 CALL cgecon(
'1', -1, a, 1, anrm, rcond, w, r, info )
231 CALL chkxer(
'CGECON', infot, nout, lerr, ok )
233 CALL cgecon(
'1', 2, a, 1, anrm, rcond, w, r, info )
234 CALL chkxer(
'CGECON', infot, nout, lerr, ok )
240 CALL cgeequ( -1, 0, a, 1, r1, r2, rcond, ccond, anrm, info )
241 CALL chkxer(
'CGEEQU', infot, nout, lerr, ok )
243 CALL cgeequ( 0, -1, a, 1, r1, r2, rcond, ccond, anrm, info )
244 CALL chkxer(
'CGEEQU', infot, nout, lerr, ok )
246 CALL cgeequ( 2, 2, a, 1, r1, r2, rcond, ccond, anrm, info )
247 CALL chkxer(
'CGEEQU', infot, nout, lerr, ok )
252 ELSE IF( lsamen( 2, c2,
'GB' ) )
THEN
258 CALL cgbtrf( -1, 0, 0, 0, a, 1, ip, info )
259 CALL chkxer(
'CGBTRF', infot, nout, lerr, ok )
261 CALL cgbtrf( 0, -1, 0, 0, a, 1, ip, info )
262 CALL chkxer(
'CGBTRF', infot, nout, lerr, ok )
264 CALL cgbtrf( 1, 1, -1, 0, a, 1, ip, info )
265 CALL chkxer(
'CGBTRF', infot, nout, lerr, ok )
267 CALL cgbtrf( 1, 1, 0, -1, a, 1, ip, info )
268 CALL chkxer(
'CGBTRF', infot, nout, lerr, ok )
270 CALL cgbtrf( 2, 2, 1, 1, a, 3, ip, info )
271 CALL chkxer(
'CGBTRF', infot, nout, lerr, ok )
277 CALL cgbtf2( -1, 0, 0, 0, a, 1, ip, info )
278 CALL chkxer(
'CGBTF2', infot, nout, lerr, ok )
280 CALL cgbtf2( 0, -1, 0, 0, a, 1, ip, info )
281 CALL chkxer(
'CGBTF2', infot, nout, lerr, ok )
283 CALL cgbtf2( 1, 1, -1, 0, a, 1, ip, info )
284 CALL chkxer(
'CGBTF2', infot, nout, lerr, ok )
286 CALL cgbtf2( 1, 1, 0, -1, a, 1, ip, info )
287 CALL chkxer(
'CGBTF2', infot, nout, lerr, ok )
289 CALL cgbtf2( 2, 2, 1, 1, a, 3, ip, info )
290 CALL chkxer(
'CGBTF2', infot, nout, lerr, ok )
296 CALL cgbtrs(
'/', 0, 0, 0, 1, a, 1, ip, b, 1, info )
297 CALL chkxer(
'CGBTRS', infot, nout, lerr, ok )
299 CALL cgbtrs(
'N', -1, 0, 0, 1, a, 1, ip, b, 1, info )
300 CALL chkxer(
'CGBTRS', infot, nout, lerr, ok )
302 CALL cgbtrs(
'N', 1, -1, 0, 1, a, 1, ip, b, 1, info )
303 CALL chkxer(
'CGBTRS', infot, nout, lerr, ok )
305 CALL cgbtrs(
'N', 1, 0, -1, 1, a, 1, ip, b, 1, info )
306 CALL chkxer(
'CGBTRS', infot, nout, lerr, ok )
308 CALL cgbtrs(
'N', 1, 0, 0, -1, a, 1, ip, b, 1, info )
309 CALL chkxer(
'CGBTRS', infot, nout, lerr, ok )
311 CALL cgbtrs(
'N', 2, 1, 1, 1, a, 3, ip, b, 2, info )
312 CALL chkxer(
'CGBTRS', infot, nout, lerr, ok )
314 CALL cgbtrs(
'N', 2, 0, 0, 1, a, 1, ip, b, 1, info )
315 CALL chkxer(
'CGBTRS', infot, nout, lerr, ok )
321 CALL cgbrfs(
'/', 0, 0, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
323 CALL chkxer(
'CGBRFS', infot, nout, lerr, ok )
325 CALL cgbrfs(
'N', -1, 0, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
327 CALL chkxer(
'CGBRFS', infot, nout, lerr, ok )
329 CALL cgbrfs(
'N', 1, -1, 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
331 CALL chkxer(
'CGBRFS', infot, nout, lerr, ok )
333 CALL cgbrfs(
'N', 1, 0, -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1,
335 CALL chkxer(
'CGBRFS', infot, nout, lerr, ok )
337 CALL cgbrfs(
'N', 1, 0, 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1,
339 CALL chkxer(
'CGBRFS', infot, nout, lerr, ok )
341 CALL cgbrfs(
'N', 2, 1, 1, 1, a, 2, af, 4, ip, b, 2, x, 2, r1,
343 CALL chkxer(
'CGBRFS', infot, nout, lerr, ok )
345 CALL cgbrfs(
'N', 2, 1, 1, 1, a, 3, af, 3, ip, b, 2, x, 2, r1,
347 CALL chkxer(
'CGBRFS', infot, nout, lerr, ok )
349 CALL cgbrfs(
'N', 2, 0, 0, 1, a, 1, af, 1, ip, b, 1, x, 2, r1,
351 CALL chkxer(
'CGBRFS', infot, nout, lerr, ok )
353 CALL cgbrfs(
'N', 2, 0, 0, 1, a, 1, af, 1, ip, b, 2, x, 1, r1,
355 CALL chkxer(
'CGBRFS', infot, nout, lerr, ok )
361 CALL cgbcon(
'/', 0, 0, 0, a, 1, ip, anrm, rcond, w, r, info )
362 CALL chkxer(
'CGBCON', infot, nout, lerr, ok )
364 CALL cgbcon(
'1', -1, 0, 0, a, 1, ip, anrm, rcond, w, r, info )
365 CALL chkxer(
'CGBCON', infot, nout, lerr, ok )
367 CALL cgbcon(
'1', 1, -1, 0, a, 1, ip, anrm, rcond, w, r, info )
368 CALL chkxer(
'CGBCON', infot, nout, lerr, ok )
370 CALL cgbcon(
'1', 1, 0, -1, a, 1, ip, anrm, rcond, w, r, info )
371 CALL chkxer(
'CGBCON', infot, nout, lerr, ok )
373 CALL cgbcon(
'1', 2, 1, 1, a, 3, ip, anrm, rcond, w, r, info )
374 CALL chkxer(
'CGBCON', infot, nout, lerr, ok )
380 CALL cgbequ( -1, 0, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
382 CALL chkxer(
'CGBEQU', infot, nout, lerr, ok )
384 CALL cgbequ( 0, -1, 0, 0, a, 1, r1, r2, rcond, ccond, anrm,
386 CALL chkxer(
'CGBEQU', infot, nout, lerr, ok )
388 CALL cgbequ( 1, 1, -1, 0, a, 1, r1, r2, rcond, ccond, anrm,
390 CALL chkxer(
'CGBEQU', infot, nout, lerr, ok )
392 CALL cgbequ( 1, 1, 0, -1, a, 1, r1, r2, rcond, ccond, anrm,
394 CALL chkxer(
'CGBEQU', infot, nout, lerr, ok )
396 CALL cgbequ( 2, 2, 1, 1, a, 2, r1, r2, rcond, ccond, anrm,
398 CALL chkxer(
'CGBEQU', infot, nout, lerr, ok )
403 CALL alaesm( path, ok, nout )
subroutine cgbtrf(M, N, KL, KU, AB, LDAB, IPIV, INFO)
CGBTRF
subroutine cgetri(N, A, LDA, IPIV, WORK, LWORK, INFO)
CGETRI
subroutine cgerfs(TRANS, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CGERFS
subroutine alaesm(PATH, OK, NOUT)
ALAESM
subroutine cgetrs(TRANS, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CGETRS
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
subroutine cgeequ(M, N, A, LDA, R, C, ROWCND, COLCND, AMAX, INFO)
CGEEQU
subroutine cgbcon(NORM, N, KL, KU, AB, LDAB, IPIV, ANORM, RCOND, WORK, RWORK, INFO)
CGBCON
subroutine cgetrf(M, N, A, LDA, IPIV, INFO)
CGETRF
subroutine cgbequ(M, N, KL, KU, AB, LDAB, R, C, ROWCND, COLCND, AMAX, INFO)
CGBEQU
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...
subroutine cgbrfs(TRANS, N, KL, KU, NRHS, AB, LDAB, AFB, LDAFB, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CGBRFS
subroutine cgecon(NORM, N, A, LDA, ANORM, RCOND, WORK, RWORK, INFO)
CGECON
subroutine cerrge(PATH, NUNIT)
CERRGE
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...
subroutine cgbtrs(TRANS, N, KL, KU, NRHS, AB, LDAB, IPIV, B, LDB, INFO)
CGBTRS