151 SUBROUTINE schkps( DOTYPE, NN, NVAL, NNB, NBVAL, NRANK, RANKVAL,
152 $ THRESH, TSTERR, NMAX, A, AFAC, PERM, PIV, WORK,
161 INTEGER NMAX, NN, NNB, NOUT, NRANK
165 REAL A( * ), AFAC( * ), PERM( * ), RWORK( * ),
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 ) =
'Single Precision'
221 iseed( i ) = iseedy( i )
227 $
CALL serrps( path, nout )
241 DO 140 imat = 1, nimat
245 IF( .NOT.dotype( imat ) )
250 DO 130 irank = 1, nrank
255 IF( ( imat.LT.3 .OR. imat.GT.5 ) .AND. irank.GT.1 )
258 rank = ceiling( ( n * real( rankval( irank ) ) )
265 uplo = uplos( iuplo )
270 CALL slatb5( path, imat, n,
TYPE, kl, ku, anorm,
271 $ mode, cndnum, dist )
274 CALL slatmt( n, n, dist, iseed,
TYPE, rwork, mode,
275 $ cndnum, anorm, rank, kl, ku, uplo, a,
281 CALL alaerh( path,
'SLATMT', info, 0, uplo, n,
282 $ n, -1, -1, -1, imat, nfail, nerrs,
296 CALL slacpy( uplo, n, n, a, lda, afac, lda )
302 CALL spstrf( uplo, n, afac, lda, piv, comprank,
308 $ .OR.(info.NE.izero.AND.rank.EQ.n)
309 $ .OR.(info.LE.izero.AND.rank.LT.n) )
THEN
310 CALL alaerh( path,
'SPSTRF', info, izero,
311 $ uplo, n, n, -1, -1, nb, imat,
312 $ nfail, nerrs, nout )
325 CALL spst01( uplo, n, a, lda, afac, lda, perm, lda,
326 $ piv, rwork, result, comprank )
333 rankdiff = rank - comprank
334 IF( result.GE.thresh )
THEN
335 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
336 $
CALL alahd( nout, path )
337 WRITE( nout, fmt = 9999 )uplo, n, rank,
338 $ rankdiff, nb, imat, result
351 CALL alasum( path, nout, nfail, nrun, nerrs )
353 9999
FORMAT(
' UPLO = ''', a1,
''', N =', i5,
', RANK =', i3,
354 $
', 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 slacpy(uplo, m, n, a, lda, b, ldb)
SLACPY copies all or part of one two-dimensional array to another.
subroutine spstrf(uplo, n, a, lda, piv, rank, tol, work, info)
SPSTRF computes the Cholesky factorization with complete pivoting of a real symmetric positive semide...
subroutine schkps(dotype, nn, nval, nnb, nbval, nrank, rankval, thresh, tsterr, nmax, a, afac, perm, piv, work, rwork, nout)
SCHKPS
subroutine serrps(path, nunit)
SERRPS
subroutine slatb5(path, imat, n, type, kl, ku, anorm, mode, cndnum, dist)
SLATB5
subroutine slatmt(m, n, dist, iseed, sym, d, mode, cond, dmax, rank, kl, ku, pack, a, lda, work, info)
SLATMT
subroutine spst01(uplo, n, a, lda, afac, ldafac, perm, ldperm, piv, rwork, resid, rank)
SPST01