198 SUBROUTINE zchkqr( 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
209 DOUBLE PRECISION THRESH
213 INTEGER IWORK( * ), MVAL( * ), NBVAL( * ), NVAL( * ),
215 DOUBLE PRECISION RWORK( * )
216 COMPLEX*16 A( * ), AC( * ), AF( * ), AQ( * ), AR( * ),
217 $ b( * ), tau( * ), work( * ), x( * ), xact( * )
224 PARAMETER ( NTESTS = 9 )
226 parameter( ntypes = 8 )
227 DOUBLE PRECISION ZERO
228 parameter( zero = 0.0d0 )
233 INTEGER I, IK, IM, IMAT, IN, INB, INFO, K, KL, KU, LDA,
234 $ lwork, m, minmn, mode, n, nb, nerrs, nfail, nk,
236 DOUBLE PRECISION ANORM, CNDNUM
239 INTEGER ISEED( 4 ), ISEEDY( 4 ), KVAL( 4 )
240 DOUBLE PRECISION RESULT( NTESTS )
260 COMMON / infoc / infot, nunit, ok, lerr
261 COMMON / srnamc / srnamt
264 DATA iseedy / 1988, 1989, 1990, 1991 /
270 path( 1: 1 ) =
'Zomplex precision'
276 iseed( i ) = iseedy( i )
282 $
CALL zerrqr( path, nout )
287 lwork = nmax*max( nmax, nrhs )
299 DO 50 imat = 1, ntypes
303 IF( .NOT.dotype( imat ) )
309 CALL zlatb4( path, imat, m, n,
TYPE, kl, ku, anorm, mode,
313 CALL zlatms( m, n, dist, iseed,
TYPE, rwork, mode,
314 $ cndnum, anorm, kl, ku,
'No packing', a, lda,
320 CALL alaerh( path,
'ZLATMS', info, 0,
' ', m, n, -1,
321 $ -1, -1, imat, nfail, nerrs, nout )
332 kval( 4 ) = minmn / 2
333 IF( minmn.EQ.0 )
THEN
335 ELSE IF( minmn.EQ.1 )
THEN
337 ELSE IF( minmn.LE.3 )
THEN
363 CALL zqrt01( m, n, a, af, aq, ar, lda, tau,
364 $ work, lwork, rwork, result( 1 ) )
368 CALL zqrt01p( m, n, a, af, aq, ar, lda, tau,
369 $ work, lwork, rwork, result( 8 ) )
371 IF( .NOT. zgennd( m, n, af, lda ) )
372 $ result( 9 ) = 2*thresh
374 ELSE IF( m.GE.n )
THEN
379 CALL zqrt02( m, n, k, a, af, aq, ar, lda, tau,
380 $ work, lwork, rwork, result( 1 ) )
387 CALL zqrt03( m, n, k, af, ac, ar, aq, lda, tau,
388 $ work, lwork, rwork, result( 3 ) )
395 IF( k.EQ.n .AND. inb.EQ.1 )
THEN
401 CALL zlarhs( path,
'New',
'Full',
402 $
'No transpose', m, n, 0, 0,
403 $ nrhs, a, lda, xact, lda, b, lda,
406 CALL zlacpy(
'Full', m, nrhs, b, lda, x,
412 CALL zlacpy(
'Full', m, n, a, lda, af, lda )
415 CALL zgels(
'No transpose', m, n, nrhs, af,
416 $ lda, x, lda, work, lwork, info )
421 $
CALL alaerh( path,
'ZGELS', info, 0,
'N',
422 $ m, n, nrhs, -1, nb, imat,
423 $ nfail, nerrs, nout )
425 CALL zget02(
'No transpose', m, n, nrhs, a,
426 $ lda, x, lda, b, lda, rwork,
436 IF( result( i ).GE.thresh )
THEN
437 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
438 $
CALL alahd( nout, path )
439 WRITE( nout, fmt = 9999 )m, n, k, nb, nx,
440 $ imat, i, result( i )
453 CALL alasum( path, nout, nfail, nrun, nerrs )
455 9999
FORMAT(
' M=', i5,
', N=', i5,
', K=', i5,
', NB=', i4,
', NX=',
456 $ i5,
', type ', i2,
', test(', i2,
')=', g12.5 )
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
subroutine xlaenv(ispec, nvalue)
XLAENV
subroutine zget02(trans, m, n, nrhs, a, lda, x, ldx, b, ldb, rwork, resid)
ZGET02
subroutine zlarhs(path, xtype, uplo, trans, m, n, kl, ku, nrhs, a, lda, x, ldx, b, ldb, iseed, info)
ZLARHS
subroutine alaerh(path, subnam, info, infoe, opts, m, n, kl, ku, n5, imat, nfail, nerrs, nout)
ALAERH
subroutine alahd(iounit, path)
ALAHD
subroutine zgels(trans, m, n, nrhs, a, lda, b, ldb, work, lwork, info)
ZGELS solves overdetermined or underdetermined systems for GE matrices
subroutine zlacpy(uplo, m, n, a, lda, b, ldb)
ZLACPY copies all or part of one two-dimensional array to another.
subroutine zchkqr(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)
ZCHKQR
subroutine zerrqr(path, nunit)
ZERRQR
subroutine zlatb4(path, imat, m, n, type, kl, ku, anorm, mode, cndnum, dist)
ZLATB4
subroutine zlatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
ZLATMS
subroutine zqrt01(m, n, a, af, q, r, lda, tau, work, lwork, rwork, result)
ZQRT01
subroutine zqrt01p(m, n, a, af, q, r, lda, tau, work, lwork, rwork, result)
ZQRT01P
subroutine zqrt02(m, n, k, a, af, q, r, lda, tau, work, lwork, rwork, result)
ZQRT02
subroutine zqrt03(m, n, k, af, c, cc, q, lda, tau, work, lwork, rwork, result)
ZQRT03