151 SUBROUTINE cchkps( DOTYPE, NN, NVAL, NNB, NBVAL, NRANK, RANKVAL,
152 $ THRESH, TSTERR, NMAX, A, AFAC, PERM, PIV, WORK,
161 INTEGER NMAX, NN, NNB, NOUT, NRANK
165 COMPLEX A( * ), AFAC( * ), PERM( * ), WORK( * )
167 INTEGER NBVAL( * ), NVAL( * ), PIV( * ), RANKVAL( * )
175 PARAMETER ( ONE = 1.0e+0 )
177 parameter( ntypes = 9 )
180 REAL ANORM, CNDNUM, RESULT, TOL
181 INTEGER COMPRANK, I, IMAT, IN, INB, INFO, IRANK, IUPLO,
182 $ izero, kl, ku, lda, mode, n, nb, nerrs, nfail,
183 $ nimat, nrun, rank, rankdiff
184 CHARACTER DIST,
TYPE, UPLO
188 INTEGER ISEED( 4 ), ISEEDY( 4 )
201 COMMON / infoc / infot, nunit, ok, lerr
202 COMMON / srnamc / srnamt
205 INTRINSIC max, real, ceiling
208 DATA iseedy / 1988, 1989, 1990, 1991 /
209 DATA uplos /
'U',
'L' /
215 path( 1: 1 ) =
'Complex Precision'
221 iseed( i ) = iseedy( i )
227 $
CALL cerrps( path, nout )
240 DO 140 imat = 1, nimat
244 IF( .NOT.dotype( imat ) )
249 DO 130 irank = 1, nrank
254 IF( ( imat.LT.3 .OR. imat.GT.5 ) .AND. irank.GT.1 )
257 rank = ceiling( ( n * real( rankval( irank ) ) )
264 uplo = uplos( iuplo )
269 CALL clatb5( path, imat, n,
TYPE, kl, ku, anorm,
270 $ mode, cndnum, dist )
273 CALL clatmt( n, n, dist, iseed,
TYPE, rwork, mode,
274 $ cndnum, anorm, rank, kl, ku, uplo, a,
280 CALL alaerh( path,
'CLATMT', info, 0, uplo, n,
281 $ n, -1, -1, -1, imat, nfail, nerrs,
295 CALL clacpy( uplo, n, n, a, lda, afac, lda )
301 CALL cpstrf( uplo, n, afac, lda, piv, comprank,
307 $ .OR.(info.NE.izero.AND.rank.EQ.n)
308 $ .OR.(info.LE.izero.AND.rank.LT.n) )
THEN
309 CALL alaerh( path,
'CPSTRF', info, izero,
310 $ uplo, n, n, -1, -1, nb, imat,
311 $ nfail, nerrs, nout )
324 CALL cpst01( uplo, n, a, lda, afac, lda, perm, lda,
325 $ piv, rwork, result, comprank )
332 rankdiff = rank - comprank
333 IF( result.GE.thresh )
THEN
334 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
335 $
CALL alahd( nout, path )
336 WRITE( nout, fmt = 9999 )uplo, n, rank,
337 $ rankdiff, nb, imat, result
350 CALL alasum( path, nout, nfail, nrun, nerrs )
352 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', RANK =', i3,
353 $
', Diff =', i5,
', NB =', i4,
', type ', i2,
', Ratio =',
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
subroutine xlaenv(ispec, nvalue)
XLAENV
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine cchkps(dotype, nn, nval, nnb, nbval, nrank, rankval, thresh, tsterr, nmax, a, afac, perm, piv, work, rwork, nout)
CCHKPS
subroutine cerrps(path, nunit)
CERRPS
subroutine clatb5(path, imat, n, type, kl, ku, anorm, mode, cndnum, dist)
CLATB5
subroutine clatmt(m, n, dist, iseed, sym, d, mode, cond, dmax, rank, kl, ku, pack, a, lda, work, info)
CLATMT
subroutine cpst01(uplo, n, a, lda, afac, ldafac, perm, ldperm, piv, rwork, resid, rank)
CPST01
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
subroutine cpstrf(uplo, n, a, lda, piv, rank, tol, work, info)
CPSTRF computes the Cholesky factorization with complete pivoting of complex Hermitian positive semid...