100 SUBROUTINE zchklqtp( THRESH, TSTERR, NM, MVAL, NN, NVAL, NNB,
110 INTEGER NM, NN, NNB, NOUT
111 DOUBLE PRECISION THRESH
114 INTEGER MVAL( * ), NBVAL( * ), NVAL( * )
121 parameter( ntests = 6 )
125 INTEGER I, J, K, L, T, M, N, NB, NFAIL, NERRS, NRUN,
129 DOUBLE PRECISION RESULT( NTESTS )
140 COMMON / infoc / infot, nunit, ok, lerr
141 COMMON / srnamc / srnamt
155 IF( tsterr )
CALL zerrlqtp( path, nout )
171 DO l = 0, minmn, max( minmn, 1 )
180 IF( (nb.LE.m).AND.(nb.GT.0) )
THEN
181 CALL zlqt05( m, n, l, nb, result )
187 IF( result( t ).GE.thresh )
THEN
188 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
189 $
CALL alahd( nout, path )
190 WRITE( nout, fmt = 9999 )m, n, nb, l,
204 CALL alasum( path, nout, nfail, nrun, nerrs )
206 9999
FORMAT(
' M=', i5,
', N=', i5,
', NB=', i4,
' L=', i4,
207 $
' 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 zchklqtp(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
ZCHKLQTP
subroutine zerrlqtp(path, nunit)
ZERRLQTP
subroutine zlqt04(m, n, nb, result)
DLQT04
subroutine zlqt05(m, n, l, nb, result)
ZLQT05