198 SUBROUTINE cchkrq( DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL,
199 $ NRHS, THRESH, TSTERR, NMAX, A, AF, AQ, AR, AC,
200 $ B, X, XACT, TAU, WORK, RWORK, IWORK, NOUT )
208 INTEGER NM, NMAX, NN, NNB, NOUT, NRHS
213 INTEGER IWORK( * ), MVAL( * ), NBVAL( * ), NVAL( * ),
216 COMPLEX A( * ), AC( * ), AF( * ), AQ( * ), AR( * ),
217 $ b( * ), tau( * ), work( * ), x( * ), xact( * )
224 PARAMETER ( NTESTS = 7 )
226 parameter( ntypes = 8 )
228 parameter( zero = 0.0e0 )
233 INTEGER I, IK, IM, IMAT, IN, INB, INFO, K, KL, KU, LDA,
234 $ lwork, m, minmn, mode, n, nb, nerrs, nfail, nk,
239 INTEGER ISEED( 4 ), ISEEDY( 4 ), KVAL( 4 )
240 REAL RESULT( NTESTS )
256 COMMON / infoc / infot, nunit, ok, lerr
257 COMMON / srnamc / srnamt
260 DATA iseedy / 1988, 1989, 1990, 1991 /
266 path( 1: 1 ) =
'Complex precision'
272 iseed( i ) = iseedy( i )
278 $
CALL cerrrq( path, nout )
283 lwork = nmax*max( nmax, nrhs )
295 DO 50 imat = 1, ntypes
299 IF( .NOT.dotype( imat ) )
305 CALL clatb4( path, imat, m, n,
TYPE, kl, ku, anorm, mode,
309 CALL clatms( m, n, dist, iseed,
TYPE, rwork, mode,
310 $ cndnum, anorm, kl, ku,
'No packing', a, lda,
316 CALL alaerh( path,
'CLATMS', info, 0,
' ', m, n, -1,
317 $ -1, -1, imat, nfail, nerrs, nout )
328 kval( 4 ) = minmn / 2
329 IF( minmn.EQ.0 )
THEN
331 ELSE IF( minmn.EQ.1 )
THEN
333 ELSE IF( minmn.LE.3 )
THEN
359 CALL crqt01( m, n, a, af, aq, ar, lda, tau,
360 $ work, lwork, rwork, result( 1 ) )
361 ELSE IF( m.LE.n )
THEN
366 CALL crqt02( m, n, k, a, af, aq, ar, lda, tau,
367 $ work, lwork, rwork, result( 1 ) )
374 CALL crqt03( m, n, k, af, ac, ar, aq, lda, tau,
375 $ work, lwork, rwork, result( 3 ) )
382 IF( k.EQ.m .AND. inb.EQ.1 )
THEN
388 CALL clarhs( path,
'New',
'Full',
389 $
'No transpose', m, n, 0, 0,
390 $ nrhs, a, lda, xact, lda, b, lda,
393 CALL clacpy(
'Full', m, nrhs, b, lda,
396 CALL cgerqs( m, n, nrhs, af, lda, tau, x,
397 $ lda, work, lwork, info )
402 $
CALL alaerh( path,
'CGERQS', info, 0,
' ',
403 $ m, n, nrhs, -1, nb, imat,
404 $ nfail, nerrs, nout )
406 CALL cget02(
'No transpose', m, n, nrhs, a,
407 $ lda, x, lda, b, lda, rwork,
417 IF( result( i ).GE.thresh )
THEN
418 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
419 $
CALL alahd( nout, path )
420 WRITE( nout, fmt = 9999 )m, n, k, nb, nx,
421 $ imat, i, result( i )
434 CALL alasum( path, nout, nfail, nrun, nerrs )
436 9999
FORMAT(
' M=', i5,
', N=', i5,
', K=', i5,
', NB=', i4,
', NX=',
437 $ i5,
', type ', i2,
', test(', i2,
')=', g12.5 )
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
subroutine cget02(trans, m, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
CGET02
subroutine clarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
CLARHS
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 cchkrq(dotype, nm, mval, nn, nval, nnb, nbval, nxval, nrhs, thresh, tsterr, nmax, a, af, aq, ar, ac, b, x, xact, tau, work, rwork, iwork, nout)
CCHKRQ
subroutine cerrrq(path, nunit)
CERRRQ
subroutine cgerqs(m, n, nrhs, a, lda, tau, b, ldb, work, lwork, info)
CGERQS
subroutine clatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
CLATB4
subroutine clatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
CLATMS
subroutine crqt01(m, n, a, af, q, r, lda, tau, work, lwork, rwork, result)
CRQT01
subroutine crqt02(m, n, k, a, af, q, r, lda, tau, work, lwork, rwork, result)
CRQT02
subroutine crqt03(m, n, k, af, c, cc, q, lda, tau, work, lwork, rwork, result)
CRQT03
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.