56 SUBROUTINE zerrps( PATH, NUNIT )
72 parameter ( nmax = 4 )
75 INTEGER I, INFO, J, RANK
78 COMPLEX*16 A( nmax, nmax )
79 DOUBLE PRECISION RWORK( 2*nmax )
91 COMMON / infoc / infot, nout, ok, lerr
92 COMMON / srnamc / srnamt
100 WRITE( nout, fmt = * )
106 a( i, j ) = 1.d0 / dble( i+j )
111 rwork( nmax+j ) = 0.d0
124 CALL zpstrf(
'/', 0, a, 1, piv, rank, -1.d0, rwork, info )
125 CALL chkxer(
'ZPSTRF', infot, nout, lerr, ok )
127 CALL zpstrf(
'U', -1, a, 1, piv, rank, -1.d0, rwork, info )
128 CALL chkxer(
'ZPSTRF', infot, nout, lerr, ok )
130 CALL zpstrf(
'U', 2, a, 1, piv, rank, -1.d0, rwork, info )
131 CALL chkxer(
'ZPSTRF', infot, nout, lerr, ok )
137 CALL zpstf2(
'/', 0, a, 1, piv, rank, -1.d0, rwork, info )
138 CALL chkxer(
'ZPSTF2', infot, nout, lerr, ok )
140 CALL zpstf2(
'U', -1, a, 1, piv, rank, -1.d0, rwork, info )
141 CALL chkxer(
'ZPSTF2', infot, nout, lerr, ok )
143 CALL zpstf2(
'U', 2, a, 1, piv, rank, -1.d0, rwork, info )
144 CALL chkxer(
'ZPSTF2', infot, nout, lerr, ok )
149 CALL alaesm( path, ok, nout )
subroutine zerrps(PATH, NUNIT)
ZERRPS
subroutine alaesm(PATH, OK, NOUT)
ALAESM
subroutine chkxer(SRNAMT, INFOT, NOUT, LERR, OK)
subroutine zpstf2(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)
ZPSTF2 computes the Cholesky factorization with complete pivoting of a complex Hermitian positive sem...
subroutine zpstrf(UPLO, N, A, LDA, PIV, RANK, TOL, WORK, INFO)
ZPSTRF computes the Cholesky factorization with complete pivoting of a complex Hermitian positive sem...