153 SUBROUTINE schkps( DOTYPE, NN, NVAL, NNB, NBVAL, NRANK, RANKVAL,
154 $ thresh, tsterr, nmax, a, afac, perm, piv, work,
164 INTEGER nmax, nn, nnb, nout, nrank
168 REAL a( * ), afac( * ), perm( * ), rwork( * ),
170 INTEGER nbval( * ), nval( * ), piv( * ), rankval( * )
178 parameter( one = 1.0e+0 )
180 parameter( ntypes = 9 )
183 REAL anorm, cndnum, result, tol
184 INTEGER comprank, i, imat, in, inb, info, irank, iuplo,
185 $ izero, kl, ku, lda, mode, n, nb, nerrs, nfail,
186 $ nimat, nrun, rank, rankdiff
187 CHARACTER dist, type, uplo
191 INTEGER iseed( 4 ), iseedy( 4 )
204 common / infoc / infot, nunit, ok, lerr
205 common / srnamc / srnamt
208 INTRINSIC max,
REAL, ceiling
211 DATA iseedy / 1988, 1989, 1990, 1991 /
212 DATA uplos /
'U',
'L' /
218 path( 1: 1 ) =
'Single Precision'
224 iseed( i ) = iseedy( i )
230 $ CALL
serrps( path, nout )
244 DO 140 imat = 1, nimat
248 IF( .NOT.dotype( imat ) )
253 DO 130 irank = 1, nrank
258 IF( ( imat.LT.3 .OR. imat.GT.5 ) .AND. irank.GT.1 )
261 rank = ceiling( ( n *
REAL( RANKVAL( IRANK ) ) )
268 uplo = uplos( iuplo )
273 CALL
slatb5( path, imat, n, type, kl, ku, anorm,
274 $ mode, cndnum, dist )
277 CALL
slatmt( n, n, dist, iseed, type, rwork, mode,
278 $ cndnum, anorm, rank, kl, ku, uplo, a,
284 CALL
alaerh( path,
'SLATMT', info, 0, uplo, n,
285 $ n, -1, -1, -1, imat, nfail, nerrs,
299 CALL
slacpy( uplo, n, n, a, lda, afac, lda )
305 CALL
spstrf( uplo, n, afac, lda, piv, comprank,
311 $ .OR.(info.NE.izero.AND.rank.EQ.n)
312 $ .OR.(info.LE.izero.AND.rank.LT.n) )
THEN
313 CALL
alaerh( path,
'SPSTRF', info, izero,
314 $ uplo, n, n, -1, -1, nb, imat,
315 $ nfail, nerrs, nout )
328 CALL
spst01( uplo, n, a, lda, afac, lda, perm, lda,
329 $ piv, rwork, result, comprank )
336 rankdiff = rank - comprank
337 IF( result.GE.thresh )
THEN
338 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
339 $ CALL
alahd( nout, path )
340 WRITE( nout, fmt = 9999 )uplo, n, rank,
341 $ rankdiff, nb, imat, result
354 CALL
alasum( path, nout, nfail, nrun, nerrs )
356 9999 format(
' UPLO = ''', a1,
''', N =', i5,
', RANK =', i3,
357 $
', Diff =', i5,
', NB =', i4,
', type ', i2,
', Ratio =',