100 SUBROUTINE cchkqrtp( THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB,
110 INTEGER NM, NN, NNB, NOUT
114 INTEGER MVAL( * ), NBVAL( * ), NVAL( * )
121 parameter( ntests = 6 )
125 INTEGER I, J, K, T, L, M, N, NB, NFAIL, NERRS, NRUN,
129 REAL RESULT( NTESTS )
140 COMMON / infoc / infot, nunit, ok, lerr
141 COMMON / srnamc / srnamt
155 IF( tsterr )
CALL cerrqrtp( path, nout )
171 DO l = 0, minmn, max( minmn, 1 )
181 IF( (nb.LE.n).AND.(nb.GT.0) )
THEN
182 CALL cqrt05( m, n, l, nb, result )
188 IF( result( t ).GE.thresh )
THEN
189 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
190 $
CALL alahd( nout, path )
191 WRITE( nout, fmt = 9999 )m, n, nb,
205 CALL alasum( path, nout, nfail, nrun, nerrs )
207 9999
FORMAT(
' M=', i5,
', N=', i5,
', NB=', i4,
208 $
' test(', i2,
')=', g12.5 )
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine cchkqrtp(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
CCHKQRTP
subroutine cerrqrtp(path, nunit)
CERRQRTP
subroutine cqrt05(m, n, l, nb, result)
CQRT05