100 SUBROUTINE cchktsqr( 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, M, N, NB, NFAIL, NERRS, NRUN, INB,
129 REAL RESULT( NTESTS )
144 COMMON / infoc / infot, nunit, ok, lerr
145 COMMON / srnamc / srnamt
161 IF( tsterr )
CALL cerrtsqr( path, nout )
173 IF (min(m,n).NE.0)
THEN
183 CALL ctsqr01(
'TS', m, n, mb, nb, result )
189 IF( result( t ).GE.thresh )
THEN
190 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
191 $
CALL alahd( nout, path )
192 WRITE( nout, fmt = 9999 )m, n, mb, nb,
213 IF (min(m,n).NE.0)
THEN
223 CALL ctsqr01(
'SW', m, n, mb, nb, result )
229 IF( result( t ).GE.thresh )
THEN
230 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
231 $
CALL alahd( nout, path )
232 WRITE( nout, fmt = 9998 )m, n, mb, nb,
246 CALL alasum( path, nout, nfail, nrun, nerrs )
248 9999
FORMAT(
'TS: M=', i5,
', N=', i5,
', MB=', i5,
249 $
', NB=', i5,
' test(', i2,
')=', g12.5 )
250 9998
FORMAT(
'SW: M=', i5,
', N=', i5,
', MB=', i5,
251 $
', NB=', i5,
' test(', i2,
')=', g12.5 )
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 cchktsqr(thresh, tsterr, nm, mval, nn, nval, nnb, nbval, nout)
CCHKQRT
subroutine cerrtsqr(path, nunit)
CERRTSQR
subroutine ctsqr01(tssw, m, n, mb, nb, result)
CTSQR01