59 SUBROUTINE cerrhe( PATH, NUNIT )
76 parameter ( nmax = 4 )
81 INTEGER i, info, j, n_err_bnds, nparams
82 REAL anrm, rcond, berr
86 REAL r( nmax ), r1( nmax ), r2( nmax ),
87 $ s( nmax ), err_bnds_n( nmax, 3 ),
88 $ err_bnds_c( nmax, 3 ), params( 1 )
89 COMPLEX a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
90 $ w( 2*nmax ), x( nmax )
109 COMMON / infoc / infot, nout, ok, lerr
110 COMMON / srnamc / srnamt
113 INTRINSIC cmplx, real
118 WRITE( nout, fmt = * )
125 a( i, j ) = cmplx( 1. /
REAL( I+J ), -1. /
REAL( I+J ) )
126 af( i, j ) = cmplx( 1. /
REAL( I+J ), -1. /
REAL( I+J ) )
143 IF(
lsamen( 2, c2,
'HE' ) )
THEN
149 CALL chetrf(
'/', 0, a, 1, ip, w, 1, info )
150 CALL chkxer(
'CHETRF', infot, nout, lerr, ok )
152 CALL chetrf(
'U', -1, a, 1, ip, w, 1, info )
153 CALL chkxer(
'CHETRF', infot, nout, lerr, ok )
155 CALL chetrf(
'U', 2, a, 1, ip, w, 4, info )
156 CALL chkxer(
'CHETRF', infot, nout, lerr, ok )
162 CALL chetf2(
'/', 0, a, 1, ip, info )
163 CALL chkxer(
'CHETF2', infot, nout, lerr, ok )
165 CALL chetf2(
'U', -1, a, 1, ip, info )
166 CALL chkxer(
'CHETF2', infot, nout, lerr, ok )
168 CALL chetf2(
'U', 2, a, 1, ip, info )
169 CALL chkxer(
'CHETF2', infot, nout, lerr, ok )
175 CALL chetri(
'/', 0, a, 1, ip, w, info )
176 CALL chkxer(
'CHETRI', infot, nout, lerr, ok )
178 CALL chetri(
'U', -1, a, 1, ip, w, info )
179 CALL chkxer(
'CHETRI', infot, nout, lerr, ok )
181 CALL chetri(
'U', 2, a, 1, ip, w, info )
182 CALL chkxer(
'CHETRI', infot, nout, lerr, ok )
188 CALL chetri2(
'/', 0, a, 1, ip, w, 1, info )
189 CALL chkxer(
'CHETRI2', infot, nout, lerr, ok )
191 CALL chetri2(
'U', -1, a, 1, ip, w, 1, info )
192 CALL chkxer(
'CHETRI2', infot, nout, lerr, ok )
194 CALL chetri2(
'U', 2, a, 1, ip, w, 1, info )
195 CALL chkxer(
'CHETRI2', infot, nout, lerr, ok )
201 CALL chetrs(
'/', 0, 0, a, 1, ip, b, 1, info )
202 CALL chkxer(
'CHETRS', infot, nout, lerr, ok )
204 CALL chetrs(
'U', -1, 0, a, 1, ip, b, 1, info )
205 CALL chkxer(
'CHETRS', infot, nout, lerr, ok )
207 CALL chetrs(
'U', 0, -1, a, 1, ip, b, 1, info )
208 CALL chkxer(
'CHETRS', infot, nout, lerr, ok )
210 CALL chetrs(
'U', 2, 1, a, 1, ip, b, 2, info )
211 CALL chkxer(
'CHETRS', infot, nout, lerr, ok )
213 CALL chetrs(
'U', 2, 1, a, 2, ip, b, 1, info )
214 CALL chkxer(
'CHETRS', infot, nout, lerr, ok )
220 CALL cherfs(
'/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
222 CALL chkxer(
'CHERFS', infot, nout, lerr, ok )
224 CALL cherfs(
'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
226 CALL chkxer(
'CHERFS', infot, nout, lerr, ok )
228 CALL cherfs(
'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
230 CALL chkxer(
'CHERFS', infot, nout, lerr, ok )
232 CALL cherfs(
'U', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
234 CALL chkxer(
'CHERFS', infot, nout, lerr, ok )
236 CALL cherfs(
'U', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
238 CALL chkxer(
'CHERFS', infot, nout, lerr, ok )
240 CALL cherfs(
'U', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
242 CALL chkxer(
'CHERFS', infot, nout, lerr, ok )
244 CALL cherfs(
'U', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
246 CALL chkxer(
'CHERFS', infot, nout, lerr, ok )
252 CALL checon(
'/', 0, a, 1, ip, anrm, rcond, w, info )
253 CALL chkxer(
'CHECON', infot, nout, lerr, ok )
255 CALL checon(
'U', -1, a, 1, ip, anrm, rcond, w, info )
256 CALL chkxer(
'CHECON', infot, nout, lerr, ok )
258 CALL checon(
'U', 2, a, 1, ip, anrm, rcond, w, info )
259 CALL chkxer(
'CHECON', infot, nout, lerr, ok )
261 CALL checon(
'U', 1, a, 1, ip, -anrm, rcond, w, info )
262 CALL chkxer(
'CHECON', infot, nout, lerr, ok )
270 CALL cherfsx(
'/', eq, 0, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
271 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
272 $ params, w, r, info )
273 CALL chkxer(
'CHERFSX', infot, nout, lerr, ok )
275 CALL cherfsx(
'U', eq, -1, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
276 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
277 $ params, w, r, info )
278 CALL chkxer(
'CHERFSX', infot, nout, lerr, ok )
281 CALL cherfsx(
'U', eq, -1, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
282 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
283 $ params, w, r, info )
284 CALL chkxer(
'CHERFSX', infot, nout, lerr, ok )
286 CALL cherfsx(
'U', eq, 0, -1, a, 1, af, 1, ip, s, b, 1, x, 1,
287 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
288 $ params, w, r, info )
289 CALL chkxer(
'CHERFSX', infot, nout, lerr, ok )
291 CALL cherfsx(
'U', eq, 2, 1, a, 1, af, 2, ip, s, b, 2, x, 2,
292 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
293 $ params, w, r, info )
294 CALL chkxer(
'CHERFSX', infot, nout, lerr, ok )
296 CALL cherfsx(
'U', eq, 2, 1, a, 2, af, 1, ip, s, b, 2, x, 2,
297 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
298 $ params, w, r, info )
299 CALL chkxer(
'CHERFSX', infot, nout, lerr, ok )
301 CALL cherfsx(
'U', eq, 2, 1, a, 2, af, 2, ip, s, b, 1, x, 2,
302 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
303 $ params, w, r, info )
304 CALL chkxer(
'CHERFSX', infot, nout, lerr, ok )
306 CALL cherfsx(
'U', eq, 2, 1, a, 2, af, 2, ip, s, b, 2, x, 1,
307 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
308 $ params, w, r, info )
309 CALL chkxer(
'CHERFSX', infot, nout, lerr, ok )
315 ELSE IF(
lsamen( 2, c2,
'HR' ) )
THEN
319 srnamt =
'CHETRF_ROOK'
322 CALL chkxer(
'CHETRF_ROOK', infot, nout, lerr, ok )
325 CALL chkxer(
'CHETRF_ROOK', infot, nout, lerr, ok )
328 CALL chkxer(
'CHETRF_ROOK', infot, nout, lerr, ok )
332 srnamt =
'CHETF2_ROOK'
335 CALL chkxer(
'CHETF2_ROOK', infot, nout, lerr, ok )
338 CALL chkxer(
'CHETF2_ROOK', infot, nout, lerr, ok )
341 CALL chkxer(
'CHETF2_ROOK', infot, nout, lerr, ok )
345 srnamt =
'CHETRI_ROOK'
348 CALL chkxer(
'CHETRI_ROOK', infot, nout, lerr, ok )
351 CALL chkxer(
'CHETRI_ROOK', infot, nout, lerr, ok )
354 CALL chkxer(
'CHETRI_ROOK', infot, nout, lerr, ok )
358 srnamt =
'CHETRS_ROOK'
360 CALL chetrs_rook(
'/', 0, 0, a, 1, ip, b, 1, info )
361 CALL chkxer(
'CHETRS_ROOK', infot, nout, lerr, ok )
363 CALL chetrs_rook(
'U', -1, 0, a, 1, ip, b, 1, info )
364 CALL chkxer(
'CHETRS_ROOK', infot, nout, lerr, ok )
366 CALL chetrs_rook(
'U', 0, -1, a, 1, ip, b, 1, info )
367 CALL chkxer(
'CHETRS_ROOK', infot, nout, lerr, ok )
369 CALL chetrs_rook(
'U', 2, 1, a, 1, ip, b, 2, info )
370 CALL chkxer(
'CHETRS_ROOK', infot, nout, lerr, ok )
372 CALL chetrs_rook(
'U', 2, 1, a, 2, ip, b, 1, info )
373 CALL chkxer(
'CHETRS_ROOK', infot, nout, lerr, ok )
377 srnamt =
'CHECON_ROOK'
379 CALL checon_rook(
'/', 0, a, 1, ip, anrm, rcond, w, info )
380 CALL chkxer(
'CHECON_ROOK', infot, nout, lerr, ok )
382 CALL checon_rook(
'U', -1, a, 1, ip, anrm, rcond, w, info )
383 CALL chkxer(
'CHECON_ROOK', infot, nout, lerr, ok )
385 CALL checon_rook(
'U', 2, a, 1, ip, anrm, rcond, w, info )
386 CALL chkxer(
'CHECON_ROOK', infot, nout, lerr, ok )
388 CALL checon_rook(
'U', 1, a, 1, ip, -anrm, rcond, w, info )
389 CALL chkxer(
'CHECON_ROOK', infot, nout, lerr, ok )
395 ELSE IF(
lsamen( 2, c2,
'HP' ) )
THEN
401 CALL chptrf(
'/', 0, a, ip, info )
402 CALL chkxer(
'CHPTRF', infot, nout, lerr, ok )
404 CALL chptrf(
'U', -1, a, ip, info )
405 CALL chkxer(
'CHPTRF', infot, nout, lerr, ok )
411 CALL chptri(
'/', 0, a, ip, w, info )
412 CALL chkxer(
'CHPTRI', infot, nout, lerr, ok )
414 CALL chptri(
'U', -1, a, ip, w, info )
415 CALL chkxer(
'CHPTRI', infot, nout, lerr, ok )
421 CALL chptrs(
'/', 0, 0, a, ip, b, 1, info )
422 CALL chkxer(
'CHPTRS', infot, nout, lerr, ok )
424 CALL chptrs(
'U', -1, 0, a, ip, b, 1, info )
425 CALL chkxer(
'CHPTRS', infot, nout, lerr, ok )
427 CALL chptrs(
'U', 0, -1, a, ip, b, 1, info )
428 CALL chkxer(
'CHPTRS', infot, nout, lerr, ok )
430 CALL chptrs(
'U', 2, 1, a, ip, b, 1, info )
431 CALL chkxer(
'CHPTRS', infot, nout, lerr, ok )
437 CALL chprfs(
'/', 0, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
439 CALL chkxer(
'CHPRFS', infot, nout, lerr, ok )
441 CALL chprfs(
'U', -1, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
443 CALL chkxer(
'CHPRFS', infot, nout, lerr, ok )
445 CALL chprfs(
'U', 0, -1, a, af, ip, b, 1, x, 1, r1, r2, w, r,
447 CALL chkxer(
'CHPRFS', infot, nout, lerr, ok )
449 CALL chprfs(
'U', 2, 1, a, af, ip, b, 1, x, 2, r1, r2, w, r,
451 CALL chkxer(
'CHPRFS', infot, nout, lerr, ok )
453 CALL chprfs(
'U', 2, 1, a, af, ip, b, 2, x, 1, r1, r2, w, r,
455 CALL chkxer(
'CHPRFS', infot, nout, lerr, ok )
461 CALL chpcon(
'/', 0, a, ip, anrm, rcond, w, info )
462 CALL chkxer(
'CHPCON', infot, nout, lerr, ok )
464 CALL chpcon(
'U', -1, a, ip, anrm, rcond, w, info )
465 CALL chkxer(
'CHPCON', infot, nout, lerr, ok )
467 CALL chpcon(
'U', 1, a, ip, -anrm, rcond, w, info )
468 CALL chkxer(
'CHPCON', infot, nout, lerr, ok )
473 CALL alaesm( path, ok, nout )
subroutine chetrs_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CHETRS_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using fac...
subroutine checon_rook(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
CHECON_ROOK estimates the reciprocal of the condition number fort HE matrices using factorization obt...
subroutine chetrf_rook(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CHETRF_ROOK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bun...
subroutine chetf2_rook(UPLO, N, A, LDA, IPIV, INFO)
CHETF2_ROOK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bun...
logical function lsamen(N, CA, CB)
LSAMEN
subroutine chprfs(UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CHPRFS
subroutine alaesm(PATH, OK, NOUT)
ALAESM
subroutine chptri(UPLO, N, AP, IPIV, WORK, INFO)
CHPTRI
subroutine chptrs(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
CHPTRS
subroutine chetf2(UPLO, N, A, LDA, IPIV, INFO)
CHETF2 computes the factorization of a complex Hermitian matrix, using the diagonal pivoting method (...
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
subroutine chetri_rook(UPLO, N, A, LDA, IPIV, WORK, INFO)
CHETRI_ROOK computes the inverse of HE matrix using the factorization obtained with the bounded Bunch...
subroutine chptrf(UPLO, N, AP, IPIV, INFO)
CHPTRF
subroutine cerrhe(PATH, NUNIT)
CERRHE
subroutine cherfsx(UPLO, EQUED, N, NRHS, A, LDA, AF, LDAF, IPIV, S, B, LDB, X, LDX, RCOND, BERR, N_ERR_BNDS, ERR_BNDS_NORM, ERR_BNDS_COMP, NPARAMS, PARAMS, WORK, RWORK, INFO)
CHERFSX
subroutine chetrs(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CHETRS
subroutine chetrf(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CHETRF
subroutine chetri(UPLO, N, A, LDA, IPIV, WORK, INFO)
CHETRI
subroutine checon(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
CHECON
subroutine chetri2(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CHETRI2
subroutine chpcon(UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO)
CHPCON
subroutine cherfs(UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
CHERFS