59 SUBROUTINE zerrsy( PATH, NUNIT )
75 parameter ( nmax = 4 )
80 INTEGER i, info, j, n_err_bnds, nparams
81 DOUBLE PRECISION anrm, rcond, berr
85 DOUBLE PRECISION r( nmax ), r1( nmax ), r2( nmax ),
86 $ s( nmax ), err_bnds_n( nmax, 3 ),
87 $ err_bnds_c( nmax, 3 ), params( 1 )
88 COMPLEX*16 a( nmax, nmax ), af( nmax, nmax ), b( nmax ),
89 $ w( 2*nmax ), x( nmax )
108 COMMON / infoc / infot, nout, ok, lerr
109 COMMON / srnamc / srnamt
112 INTRINSIC dble, dcmplx
117 WRITE( nout, fmt = * )
124 a( i, j ) = dcmplx( 1.d0 / dble( i+j ),
125 $ -1.d0 / dble( i+j ) )
126 af( i, j ) = dcmplx( 1.d0 / dble( i+j ),
127 $ -1.d0 / dble( i+j ) )
144 IF(
lsamen( 2, c2,
'SY' ) )
THEN
150 CALL zsytrf(
'/', 0, a, 1, ip, w, 1, info )
151 CALL chkxer(
'ZSYTRF', infot, nout, lerr, ok )
153 CALL zsytrf(
'U', -1, a, 1, ip, w, 1, info )
154 CALL chkxer(
'ZSYTRF', infot, nout, lerr, ok )
156 CALL zsytrf(
'U', 2, a, 1, ip, w, 4, info )
157 CALL chkxer(
'ZSYTRF', infot, nout, lerr, ok )
163 CALL zsytf2(
'/', 0, a, 1, ip, info )
164 CALL chkxer(
'ZSYTF2', infot, nout, lerr, ok )
166 CALL zsytf2(
'U', -1, a, 1, ip, info )
167 CALL chkxer(
'ZSYTF2', infot, nout, lerr, ok )
169 CALL zsytf2(
'U', 2, a, 1, ip, info )
170 CALL chkxer(
'ZSYTF2', infot, nout, lerr, ok )
176 CALL zsytri(
'/', 0, a, 1, ip, w, info )
177 CALL chkxer(
'ZSYTRI', infot, nout, lerr, ok )
179 CALL zsytri(
'U', -1, a, 1, ip, w, info )
180 CALL chkxer(
'ZSYTRI', infot, nout, lerr, ok )
182 CALL zsytri(
'U', 2, a, 1, ip, w, info )
183 CALL chkxer(
'ZSYTRI', infot, nout, lerr, ok )
189 CALL zsytri2(
'/', 0, a, 1, ip, w, 1, info )
190 CALL chkxer(
'ZSYTRI2', infot, nout, lerr, ok )
192 CALL zsytri2(
'U', -1, a, 1, ip, w, 1, info )
193 CALL chkxer(
'ZSYTRI2', infot, nout, lerr, ok )
195 CALL zsytri2(
'U', 2, a, 1, ip, w, 1, info )
196 CALL chkxer(
'ZSYTRI2', infot, nout, lerr, ok )
202 CALL zsytrs(
'/', 0, 0, a, 1, ip, b, 1, info )
203 CALL chkxer(
'ZSYTRS', infot, nout, lerr, ok )
205 CALL zsytrs(
'U', -1, 0, a, 1, ip, b, 1, info )
206 CALL chkxer(
'ZSYTRS', infot, nout, lerr, ok )
208 CALL zsytrs(
'U', 0, -1, a, 1, ip, b, 1, info )
209 CALL chkxer(
'ZSYTRS', infot, nout, lerr, ok )
211 CALL zsytrs(
'U', 2, 1, a, 1, ip, b, 2, info )
212 CALL chkxer(
'ZSYTRS', infot, nout, lerr, ok )
214 CALL zsytrs(
'U', 2, 1, a, 2, ip, b, 1, info )
215 CALL chkxer(
'ZSYTRS', infot, nout, lerr, ok )
221 CALL zsyrfs(
'/', 0, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2, w,
223 CALL chkxer(
'ZSYRFS', infot, nout, lerr, ok )
225 CALL zsyrfs(
'U', -1, 0, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
227 CALL chkxer(
'ZSYRFS', infot, nout, lerr, ok )
229 CALL zsyrfs(
'U', 0, -1, a, 1, af, 1, ip, b, 1, x, 1, r1, r2,
231 CALL chkxer(
'ZSYRFS', infot, nout, lerr, ok )
233 CALL zsyrfs(
'U', 2, 1, a, 1, af, 2, ip, b, 2, x, 2, r1, r2, w,
235 CALL chkxer(
'ZSYRFS', infot, nout, lerr, ok )
237 CALL zsyrfs(
'U', 2, 1, a, 2, af, 1, ip, b, 2, x, 2, r1, r2, w,
239 CALL chkxer(
'ZSYRFS', infot, nout, lerr, ok )
241 CALL zsyrfs(
'U', 2, 1, a, 2, af, 2, ip, b, 1, x, 2, r1, r2, w,
243 CALL chkxer(
'ZSYRFS', infot, nout, lerr, ok )
245 CALL zsyrfs(
'U', 2, 1, a, 2, af, 2, ip, b, 2, x, 1, r1, r2, w,
247 CALL chkxer(
'ZSYRFS', infot, nout, lerr, ok )
255 CALL zsyrfsx(
'/', eq, 0, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
256 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
257 $ params, w, r, info )
258 CALL chkxer(
'ZSYRFSX', infot, nout, lerr, ok )
260 CALL zsyrfsx(
'U', eq, -1, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
261 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
262 $ params, w, r, info )
263 CALL chkxer(
'ZSYRFSX', infot, nout, lerr, ok )
266 CALL zsyrfsx(
'U', eq, -1, 0, a, 1, af, 1, ip, s, b, 1, x, 1,
267 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
268 $ params, w, r, info )
269 CALL chkxer(
'ZSYRFSX', infot, nout, lerr, ok )
271 CALL zsyrfsx(
'U', eq, 0, -1, a, 1, af, 1, ip, s, b, 1, x, 1,
272 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
273 $ params, w, r, info )
274 CALL chkxer(
'ZSYRFSX', infot, nout, lerr, ok )
276 CALL zsyrfsx(
'U', eq, 2, 1, a, 1, af, 2, ip, s, b, 2, x, 2,
277 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
278 $ params, w, r, info )
279 CALL chkxer(
'ZSYRFSX', infot, nout, lerr, ok )
281 CALL zsyrfsx(
'U', eq, 2, 1, a, 2, af, 1, ip, s, b, 2, x, 2,
282 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
283 $ params, w, r, info )
284 CALL chkxer(
'ZSYRFSX', infot, nout, lerr, ok )
286 CALL zsyrfsx(
'U', eq, 2, 1, a, 2, af, 2, ip, s, b, 1, x, 2,
287 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
288 $ params, w, r, info )
289 CALL chkxer(
'ZSYRFSX', infot, nout, lerr, ok )
291 CALL zsyrfsx(
'U', eq, 2, 1, a, 2, af, 2, ip, s, b, 2, x, 1,
292 $ rcond, berr, n_err_bnds, err_bnds_n, err_bnds_c, nparams,
293 $ params, w, r, info )
294 CALL chkxer(
'ZSYRFSX', infot, nout, lerr, ok )
300 CALL zsycon(
'/', 0, a, 1, ip, anrm, rcond, w, info )
301 CALL chkxer(
'ZSYCON', infot, nout, lerr, ok )
303 CALL zsycon(
'U', -1, a, 1, ip, anrm, rcond, w, info )
304 CALL chkxer(
'ZSYCON', infot, nout, lerr, ok )
306 CALL zsycon(
'U', 2, a, 1, ip, anrm, rcond, w, info )
307 CALL chkxer(
'ZSYCON', infot, nout, lerr, ok )
309 CALL zsycon(
'U', 1, a, 1, ip, -anrm, rcond, w, info )
310 CALL chkxer(
'ZSYCON', infot, nout, lerr, ok )
316 ELSE IF(
lsamen( 2, c2,
'SR' ) )
THEN
320 srnamt =
'ZSYTRF_ROOK'
323 CALL chkxer(
'ZSYTRF_ROOK', infot, nout, lerr, ok )
326 CALL chkxer(
'ZSYTRF_ROOK', infot, nout, lerr, ok )
329 CALL chkxer(
'ZSYTRF_ROOK', infot, nout, lerr, ok )
333 srnamt =
'ZSYTF2_ROOK'
336 CALL chkxer(
'ZSYTF2_ROOK', infot, nout, lerr, ok )
339 CALL chkxer(
'ZSYTF2_ROOK', infot, nout, lerr, ok )
342 CALL chkxer(
'ZSYTF2_ROOK', infot, nout, lerr, ok )
346 srnamt =
'ZSYTRI_ROOK'
349 CALL chkxer(
'ZSYTRI_ROOK', infot, nout, lerr, ok )
352 CALL chkxer(
'ZSYTRI_ROOK', infot, nout, lerr, ok )
355 CALL chkxer(
'ZSYTRI_ROOK', infot, nout, lerr, ok )
359 srnamt =
'ZSYTRS_ROOK'
361 CALL zsytrs_rook(
'/', 0, 0, a, 1, ip, b, 1, info )
362 CALL chkxer(
'ZSYTRS_ROOK', infot, nout, lerr, ok )
364 CALL zsytrs_rook(
'U', -1, 0, a, 1, ip, b, 1, info )
365 CALL chkxer(
'ZSYTRS_ROOK', infot, nout, lerr, ok )
367 CALL zsytrs_rook(
'U', 0, -1, a, 1, ip, b, 1, info )
368 CALL chkxer(
'ZSYTRS_ROOK', infot, nout, lerr, ok )
370 CALL zsytrs_rook(
'U', 2, 1, a, 1, ip, b, 2, info )
371 CALL chkxer(
'ZSYTRS_ROOK', infot, nout, lerr, ok )
373 CALL zsytrs_rook(
'U', 2, 1, a, 2, ip, b, 1, info )
374 CALL chkxer(
'ZSYTRS_ROOK', infot, nout, lerr, ok )
378 srnamt =
'ZSYCON_ROOK'
380 CALL zsycon_rook(
'/', 0, a, 1, ip, anrm, rcond, w, info )
381 CALL chkxer(
'ZSYCON_ROOK', infot, nout, lerr, ok )
383 CALL zsycon_rook(
'U', -1, a, 1, ip, anrm, rcond, w, info )
384 CALL chkxer(
'ZSYCON_ROOK', infot, nout, lerr, ok )
386 CALL zsycon_rook(
'U', 2, a, 1, ip, anrm, rcond, w, info )
387 CALL chkxer(
'ZSYCON_ROOK', infot, nout, lerr, ok )
389 CALL zsycon_rook(
'U', 1, a, 1, ip, -anrm, rcond, w, info )
390 CALL chkxer(
'ZSYCON_ROOK', infot, nout, lerr, ok )
396 ELSE IF(
lsamen( 2, c2,
'SP' ) )
THEN
402 CALL zsptrf(
'/', 0, a, ip, info )
403 CALL chkxer(
'ZSPTRF', infot, nout, lerr, ok )
405 CALL zsptrf(
'U', -1, a, ip, info )
406 CALL chkxer(
'ZSPTRF', infot, nout, lerr, ok )
412 CALL zsptri(
'/', 0, a, ip, w, info )
413 CALL chkxer(
'ZSPTRI', infot, nout, lerr, ok )
415 CALL zsptri(
'U', -1, a, ip, w, info )
416 CALL chkxer(
'ZSPTRI', infot, nout, lerr, ok )
422 CALL zsptrs(
'/', 0, 0, a, ip, b, 1, info )
423 CALL chkxer(
'ZSPTRS', infot, nout, lerr, ok )
425 CALL zsptrs(
'U', -1, 0, a, ip, b, 1, info )
426 CALL chkxer(
'ZSPTRS', infot, nout, lerr, ok )
428 CALL zsptrs(
'U', 0, -1, a, ip, b, 1, info )
429 CALL chkxer(
'ZSPTRS', infot, nout, lerr, ok )
431 CALL zsptrs(
'U', 2, 1, a, ip, b, 1, info )
432 CALL chkxer(
'ZSPTRS', infot, nout, lerr, ok )
438 CALL zsprfs(
'/', 0, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
440 CALL chkxer(
'ZSPRFS', infot, nout, lerr, ok )
442 CALL zsprfs(
'U', -1, 0, a, af, ip, b, 1, x, 1, r1, r2, w, r,
444 CALL chkxer(
'ZSPRFS', infot, nout, lerr, ok )
446 CALL zsprfs(
'U', 0, -1, a, af, ip, b, 1, x, 1, r1, r2, w, r,
448 CALL chkxer(
'ZSPRFS', infot, nout, lerr, ok )
450 CALL zsprfs(
'U', 2, 1, a, af, ip, b, 1, x, 2, r1, r2, w, r,
452 CALL chkxer(
'ZSPRFS', infot, nout, lerr, ok )
454 CALL zsprfs(
'U', 2, 1, a, af, ip, b, 2, x, 1, r1, r2, w, r,
456 CALL chkxer(
'ZSPRFS', infot, nout, lerr, ok )
462 CALL zspcon(
'/', 0, a, ip, anrm, rcond, w, info )
463 CALL chkxer(
'ZSPCON', infot, nout, lerr, ok )
465 CALL zspcon(
'U', -1, a, ip, anrm, rcond, w, info )
466 CALL chkxer(
'ZSPCON', infot, nout, lerr, ok )
468 CALL zspcon(
'U', 1, a, ip, -anrm, rcond, w, info )
469 CALL chkxer(
'ZSPCON', infot, nout, lerr, ok )
474 CALL alaesm( path, ok, nout )
subroutine zsycon(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
ZSYCON
subroutine zsptri(UPLO, N, AP, IPIV, WORK, INFO)
ZSPTRI
subroutine zerrsy(PATH, NUNIT)
ZERRSY
subroutine zsytri_rook(UPLO, N, A, LDA, IPIV, WORK, INFO)
ZSYTRI_ROOK
subroutine zsytri(UPLO, N, A, LDA, IPIV, WORK, INFO)
ZSYTRI
subroutine zsytrf_rook(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRF_ROOK
subroutine zsptrf(UPLO, N, AP, IPIV, INFO)
ZSPTRF
logical function lsamen(N, CA, CB)
LSAMEN
subroutine alaesm(PATH, OK, NOUT)
ALAESM
subroutine zsytf2_rook(UPLO, N, A, LDA, IPIV, INFO)
ZSYTF2_ROOK computes the factorization of a complex symmetric indefinite matrix using the bounded Bun...
subroutine zsytri2(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRI2
subroutine zspcon(UPLO, N, AP, IPIV, ANORM, RCOND, WORK, INFO)
ZSPCON
subroutine zsytrf(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
ZSYTRF
subroutine zsyrfsx(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)
ZSYRFSX
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
subroutine zsycon_rook(UPLO, N, A, LDA, IPIV, ANORM, RCOND, WORK, INFO)
ZSYCON_ROOK
subroutine zsprfs(UPLO, N, NRHS, AP, AFP, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
ZSPRFS
subroutine zsptrs(UPLO, N, NRHS, AP, IPIV, B, LDB, INFO)
ZSPTRS
subroutine zsytrs_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZSYTRS_ROOK
subroutine zsyrfs(UPLO, N, NRHS, A, LDA, AF, LDAF, IPIV, B, LDB, X, LDX, FERR, BERR, WORK, RWORK, INFO)
ZSYRFS
subroutine zsytf2(UPLO, N, A, LDA, IPIV, INFO)
ZSYTF2 computes the factorization of a real symmetric indefinite matrix, using the diagonal pivoting ...
subroutine zsytrs(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
ZSYTRS