56 SUBROUTINE cerrpo( PATH, NUNIT )
72 parameter ( nmax = 4 )
80 REAL R( nmax ), R1( nmax ), R2( nmax )
81 COMPLEX A( nmax, nmax ), AF( nmax, nmax ), B( nmax ),
82 $ 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,
'PO' ) )
THEN
137 CALL cpotrf(
'/', 0, a, 1, info )
138 CALL chkxer(
'CPOTRF', infot, nout, lerr, ok )
140 CALL cpotrf(
'U', -1, a, 1, info )
141 CALL chkxer(
'CPOTRF', infot, nout, lerr, ok )
143 CALL cpotrf(
'U', 2, a, 1, info )
144 CALL chkxer(
'CPOTRF', infot, nout, lerr, ok )
150 CALL cpotf2(
'/', 0, a, 1, info )
151 CALL chkxer(
'CPOTF2', infot, nout, lerr, ok )
153 CALL cpotf2(
'U', -1, a, 1, info )
154 CALL chkxer(
'CPOTF2', infot, nout, lerr, ok )
156 CALL cpotf2(
'U', 2, a, 1, info )
157 CALL chkxer(
'CPOTF2', infot, nout, lerr, ok )
163 CALL cpotri(
'/', 0, a, 1, info )
164 CALL chkxer(
'CPOTRI', infot, nout, lerr, ok )
166 CALL cpotri(
'U', -1, a, 1, info )
167 CALL chkxer(
'CPOTRI', infot, nout, lerr, ok )
169 CALL cpotri(
'U', 2, a, 1, info )
170 CALL chkxer(
'CPOTRI', infot, nout, lerr, ok )
176 CALL cpotrs(
'/', 0, 0, a, 1, b, 1, info )
177 CALL chkxer(
'CPOTRS', infot, nout, lerr, ok )
179 CALL cpotrs(
'U', -1, 0, a, 1, b, 1, info )
180 CALL chkxer(
'CPOTRS', infot, nout, lerr, ok )
182 CALL cpotrs(
'U', 0, -1, a, 1, b, 1, info )
183 CALL chkxer(
'CPOTRS', infot, nout, lerr, ok )
185 CALL cpotrs(
'U', 2, 1, a, 1, b, 2, info )
186 CALL chkxer(
'CPOTRS', infot, nout, lerr, ok )
188 CALL cpotrs(
'U', 2, 1, a, 2, b, 1, info )
189 CALL chkxer(
'CPOTRS', infot, nout, lerr, ok )
195 CALL cporfs(
'/', 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
197 CALL chkxer(
'CPORFS', infot, nout, lerr, ok )
199 CALL cporfs(
'U', -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
201 CALL chkxer(
'CPORFS', infot, nout, lerr, ok )
203 CALL cporfs(
'U', 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w, r,
205 CALL chkxer(
'CPORFS', infot, nout, lerr, ok )
207 CALL cporfs(
'U', 2, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w, r,
209 CALL chkxer(
'CPORFS', infot, nout, lerr, ok )
211 CALL cporfs(
'U', 2, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w, r,
213 CALL chkxer(
'CPORFS', infot, nout, lerr, ok )
215 CALL cporfs(
'U', 2, 1, a, 2, af, 2, b, 1, x, 2, r1, r2, w, r,
217 CALL chkxer(
'CPORFS', infot, nout, lerr, ok )
219 CALL cporfs(
'U', 2, 1, a, 2, af, 2, b, 2, x, 1, r1, r2, w, r,
221 CALL chkxer(
'CPORFS', infot, nout, lerr, ok )
227 CALL cpocon(
'/', 0, a, 1, anrm, rcond, w, r, info )
228 CALL chkxer(
'CPOCON', infot, nout, lerr, ok )
230 CALL cpocon(
'U', -1, a, 1, anrm, rcond, w, r, info )
231 CALL chkxer(
'CPOCON', infot, nout, lerr, ok )
233 CALL cpocon(
'U', 2, a, 1, anrm, rcond, w, r, info )
234 CALL chkxer(
'CPOCON', infot, nout, lerr, ok )
236 CALL cpocon(
'U', 1, a, 1, -anrm, rcond, w, r, info )
237 CALL chkxer(
'CPOCON', infot, nout, lerr, ok )
243 CALL cpoequ( -1, a, 1, r1, rcond, anrm, info )
244 CALL chkxer(
'CPOEQU', infot, nout, lerr, ok )
246 CALL cpoequ( 2, a, 1, r1, rcond, anrm, info )
247 CALL chkxer(
'CPOEQU', infot, nout, lerr, ok )
252 ELSE IF( lsamen( 2, c2,
'PP' ) )
THEN
258 CALL cpptrf(
'/', 0, a, info )
259 CALL chkxer(
'CPPTRF', infot, nout, lerr, ok )
261 CALL cpptrf(
'U', -1, a, info )
262 CALL chkxer(
'CPPTRF', infot, nout, lerr, ok )
268 CALL cpptri(
'/', 0, a, info )
269 CALL chkxer(
'CPPTRI', infot, nout, lerr, ok )
271 CALL cpptri(
'U', -1, a, info )
272 CALL chkxer(
'CPPTRI', infot, nout, lerr, ok )
278 CALL cpptrs(
'/', 0, 0, a, b, 1, info )
279 CALL chkxer(
'CPPTRS', infot, nout, lerr, ok )
281 CALL cpptrs(
'U', -1, 0, a, b, 1, info )
282 CALL chkxer(
'CPPTRS', infot, nout, lerr, ok )
284 CALL cpptrs(
'U', 0, -1, a, b, 1, info )
285 CALL chkxer(
'CPPTRS', infot, nout, lerr, ok )
287 CALL cpptrs(
'U', 2, 1, a, b, 1, info )
288 CALL chkxer(
'CPPTRS', infot, nout, lerr, ok )
294 CALL cpprfs(
'/', 0, 0, a, af, b, 1, x, 1, r1, r2, w, r, info )
295 CALL chkxer(
'CPPRFS', infot, nout, lerr, ok )
297 CALL cpprfs(
'U', -1, 0, a, af, b, 1, x, 1, r1, r2, w, r,
299 CALL chkxer(
'CPPRFS', infot, nout, lerr, ok )
301 CALL cpprfs(
'U', 0, -1, a, af, b, 1, x, 1, r1, r2, w, r,
303 CALL chkxer(
'CPPRFS', infot, nout, lerr, ok )
305 CALL cpprfs(
'U', 2, 1, a, af, b, 1, x, 2, r1, r2, w, r, info )
306 CALL chkxer(
'CPPRFS', infot, nout, lerr, ok )
308 CALL cpprfs(
'U', 2, 1, a, af, b, 2, x, 1, r1, r2, w, r, info )
309 CALL chkxer(
'CPPRFS', infot, nout, lerr, ok )
315 CALL cppcon(
'/', 0, a, anrm, rcond, w, r, info )
316 CALL chkxer(
'CPPCON', infot, nout, lerr, ok )
318 CALL cppcon(
'U', -1, a, anrm, rcond, w, r, info )
319 CALL chkxer(
'CPPCON', infot, nout, lerr, ok )
321 CALL cppcon(
'U', 1, a, -anrm, rcond, w, r, info )
322 CALL chkxer(
'CPPCON', infot, nout, lerr, ok )
328 CALL cppequ(
'/', 0, a, r1, rcond, anrm, info )
329 CALL chkxer(
'CPPEQU', infot, nout, lerr, ok )
331 CALL cppequ(
'U', -1, a, r1, rcond, anrm, info )
332 CALL chkxer(
'CPPEQU', infot, nout, lerr, ok )
337 ELSE IF( lsamen( 2, c2,
'PB' ) )
THEN
343 CALL cpbtrf(
'/', 0, 0, a, 1, info )
344 CALL chkxer(
'CPBTRF', infot, nout, lerr, ok )
346 CALL cpbtrf(
'U', -1, 0, a, 1, info )
347 CALL chkxer(
'CPBTRF', infot, nout, lerr, ok )
349 CALL cpbtrf(
'U', 1, -1, a, 1, info )
350 CALL chkxer(
'CPBTRF', infot, nout, lerr, ok )
352 CALL cpbtrf(
'U', 2, 1, a, 1, info )
353 CALL chkxer(
'CPBTRF', infot, nout, lerr, ok )
359 CALL cpbtf2(
'/', 0, 0, a, 1, info )
360 CALL chkxer(
'CPBTF2', infot, nout, lerr, ok )
362 CALL cpbtf2(
'U', -1, 0, a, 1, info )
363 CALL chkxer(
'CPBTF2', infot, nout, lerr, ok )
365 CALL cpbtf2(
'U', 1, -1, a, 1, info )
366 CALL chkxer(
'CPBTF2', infot, nout, lerr, ok )
368 CALL cpbtf2(
'U', 2, 1, a, 1, info )
369 CALL chkxer(
'CPBTF2', infot, nout, lerr, ok )
375 CALL cpbtrs(
'/', 0, 0, 0, a, 1, b, 1, info )
376 CALL chkxer(
'CPBTRS', infot, nout, lerr, ok )
378 CALL cpbtrs(
'U', -1, 0, 0, a, 1, b, 1, info )
379 CALL chkxer(
'CPBTRS', infot, nout, lerr, ok )
381 CALL cpbtrs(
'U', 1, -1, 0, a, 1, b, 1, info )
382 CALL chkxer(
'CPBTRS', infot, nout, lerr, ok )
384 CALL cpbtrs(
'U', 0, 0, -1, a, 1, b, 1, info )
385 CALL chkxer(
'CPBTRS', infot, nout, lerr, ok )
387 CALL cpbtrs(
'U', 2, 1, 1, a, 1, b, 1, info )
388 CALL chkxer(
'CPBTRS', infot, nout, lerr, ok )
390 CALL cpbtrs(
'U', 2, 0, 1, a, 1, b, 1, info )
391 CALL chkxer(
'CPBTRS', infot, nout, lerr, ok )
397 CALL cpbrfs(
'/', 0, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
399 CALL chkxer(
'CPBRFS', infot, nout, lerr, ok )
401 CALL cpbrfs(
'U', -1, 0, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
403 CALL chkxer(
'CPBRFS', infot, nout, lerr, ok )
405 CALL cpbrfs(
'U', 1, -1, 0, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
407 CALL chkxer(
'CPBRFS', infot, nout, lerr, ok )
409 CALL cpbrfs(
'U', 0, 0, -1, a, 1, af, 1, b, 1, x, 1, r1, r2, w,
411 CALL chkxer(
'CPBRFS', infot, nout, lerr, ok )
413 CALL cpbrfs(
'U', 2, 1, 1, a, 1, af, 2, b, 2, x, 2, r1, r2, w,
415 CALL chkxer(
'CPBRFS', infot, nout, lerr, ok )
417 CALL cpbrfs(
'U', 2, 1, 1, a, 2, af, 1, b, 2, x, 2, r1, r2, w,
419 CALL chkxer(
'CPBRFS', infot, nout, lerr, ok )
421 CALL cpbrfs(
'U', 2, 0, 1, a, 1, af, 1, b, 1, x, 2, r1, r2, w,
423 CALL chkxer(
'CPBRFS', infot, nout, lerr, ok )
425 CALL cpbrfs(
'U', 2, 0, 1, a, 1, af, 1, b, 2, x, 1, r1, r2, w,
427 CALL chkxer(
'CPBRFS', infot, nout, lerr, ok )
433 CALL cpbcon(
'/', 0, 0, a, 1, anrm, rcond, w, r, info )
434 CALL chkxer(
'CPBCON', infot, nout, lerr, ok )
436 CALL cpbcon(
'U', -1, 0, a, 1, anrm, rcond, w, r, info )
437 CALL chkxer(
'CPBCON', infot, nout, lerr, ok )
439 CALL cpbcon(
'U', 1, -1, a, 1, anrm, rcond, w, r, info )
440 CALL chkxer(
'CPBCON', infot, nout, lerr, ok )
442 CALL cpbcon(
'U', 2, 1, a, 1, anrm, rcond, w, r, info )
443 CALL chkxer(
'CPBCON', infot, nout, lerr, ok )
445 CALL cpbcon(
'U', 1, 0, a, 1, -anrm, rcond, w, r, info )
446 CALL chkxer(
'CPBCON', infot, nout, lerr, ok )
452 CALL cpbequ(
'/', 0, 0, a, 1, r1, rcond, anrm, info )
453 CALL chkxer(
'CPBEQU', infot, nout, lerr, ok )
455 CALL cpbequ(
'U', -1, 0, a, 1, r1, rcond, anrm, info )
456 CALL chkxer(
'CPBEQU', infot, nout, lerr, ok )
458 CALL cpbequ(
'U', 1, -1, a, 1, r1, rcond, anrm, info )
459 CALL chkxer(
'CPBEQU', infot, nout, lerr, ok )
461 CALL cpbequ(
'U', 2, 1, a, 1, r1, rcond, anrm, info )
462 CALL chkxer(
'CPBEQU', infot, nout, lerr, ok )
467 CALL alaesm( path, ok, nout )
subroutine cpptrs(UPLO, N, NRHS, AP, B, LDB, INFO)
CPPTRS
subroutine cpotri(UPLO, N, A, LDA, INFO)
CPOTRI
subroutine cporfs(UPLO, N, NRHS, A, LDA, AF, LDAF, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CPORFS
subroutine cpbequ(UPLO, N, KD, AB, LDAB, S, SCOND, AMAX, INFO)
CPBEQU
subroutine cpbcon(UPLO, N, KD, AB, LDAB, ANORM, RCOND, WORK, RWORK, INFO)
CPBCON
subroutine alaesm(PATH, OK, NOUT)
ALAESM
subroutine cpptrf(UPLO, N, AP, INFO)
CPPTRF
subroutine cpbtf2(UPLO, N, KD, AB, LDAB, INFO)
CPBTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite band matrix (un...
subroutine cpocon(UPLO, N, A, LDA, ANORM, RCOND, WORK, RWORK, INFO)
CPOCON
subroutine cpbrfs(UPLO, N, KD, NRHS, AB, LDAB, AFB, LDAFB, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CPBRFS
subroutine cppcon(UPLO, N, AP, ANORM, RCOND, WORK, RWORK, INFO)
CPPCON
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
subroutine cpotrs(UPLO, N, NRHS, A, LDA, B, LDB, INFO)
CPOTRS
subroutine cpptri(UPLO, N, AP, INFO)
CPPTRI
subroutine cpoequ(N, A, LDA, S, SCOND, AMAX, INFO)
CPOEQU
subroutine cpprfs(UPLO, N, NRHS, AP, AFP, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CPPRFS
subroutine cpotrf(UPLO, N, A, LDA, INFO)
CPOTRF
subroutine cpotf2(UPLO, N, A, LDA, INFO)
CPOTF2 computes the Cholesky factorization of a symmetric/Hermitian positive definite matrix (unblock...
subroutine cpbtrf(UPLO, N, KD, AB, LDAB, INFO)
CPBTRF
subroutine cppequ(UPLO, N, AP, S, SCOND, AMAX, INFO)
CPPEQU
subroutine cerrpo(PATH, NUNIT)
CERRPO
subroutine cpbtrs(UPLO, N, KD, NRHS, AB, LDAB, B, LDB, INFO)
CPBTRS