193 SUBROUTINE zchklq( DOTYPE, NM, MVAL, NN, NVAL, NNB, NBVAL, NXVAL,
194 $ NRHS, THRESH, TSTERR, NMAX, A, AF, AQ, AL, AC,
195 $ B, X, XACT, TAU, WORK, RWORK, NOUT )
203 INTEGER NM, NMAX, NN, NNB, NOUT, NRHS
204 DOUBLE PRECISION THRESH
208 INTEGER MVAL( * ), NBVAL( * ), NVAL( * ),
210 DOUBLE PRECISION RWORK( * )
211 COMPLEX*16 A( * ), AC( * ), AF( * ), AL( * ), AQ( * ),
212 $ b( * ), tau( * ), work( * ), x( * ), xact( * )
219 PARAMETER ( NTESTS = 7 )
221 parameter( ntypes = 8 )
222 DOUBLE PRECISION ZERO
223 parameter( zero = 0.0d0 )
228 INTEGER I, IK, IM, IMAT, IN, INB, INFO, K, KL, KU, LDA,
229 $ lwork, m, minmn, mode, n, nb, nerrs, nfail, nk,
231 DOUBLE PRECISION ANORM, CNDNUM
234 INTEGER ISEED( 4 ), ISEEDY( 4 ), KVAL( 4 )
235 DOUBLE PRECISION RESULT( NTESTS )
251 COMMON / infoc / infot, nunit, ok, lerr
252 COMMON / srnamc / srnamt
255 DATA iseedy / 1988, 1989, 1990, 1991 /
261 path( 1: 1 ) =
'Zomplex precision'
267 iseed( i ) = iseedy( i )
273 $
CALL zerrlq( path, nout )
278 lwork = nmax*max( nmax, nrhs )
290 DO 50 imat = 1, ntypes
294 IF( .NOT.dotype( imat ) )
300 CALL zlatb4( path, imat, m, n,
TYPE, kl, ku, anorm, mode,
304 CALL zlatms( m, n, dist, iseed,
TYPE, rwork, mode,
305 $ cndnum, anorm, kl, ku,
'No packing', a, lda,
311 CALL alaerh( path,
'ZLATMS', info, 0,
' ', m, n, -1,
312 $ -1, -1, imat, nfail, nerrs, nout )
323 kval( 4 ) = minmn / 2
324 IF( minmn.EQ.0 )
THEN
326 ELSE IF( minmn.EQ.1 )
THEN
328 ELSE IF( minmn.LE.3 )
THEN
354 CALL zlqt01( m, n, a, af, aq, al, lda, tau,
355 $ work, lwork, rwork, result( 1 ) )
356 ELSE IF( m.LE.n )
THEN
361 CALL zlqt02( m, n, k, a, af, aq, al, lda, tau,
362 $ work, lwork, rwork, result( 1 ) )
369 CALL zlqt03( m, n, k, af, ac, al, aq, lda, tau,
370 $ work, lwork, rwork, result( 3 ) )
377 IF( k.EQ.m .AND. inb.EQ.1 )
THEN
383 CALL zlarhs( path,
'New',
'Full',
384 $
'No transpose', m, n, 0, 0,
385 $ nrhs, a, lda, xact, lda, b, lda,
388 CALL zlacpy(
'Full', m, nrhs, b, lda, x,
394 CALL zlacpy(
'Full', m, n, a, lda, af, lda )
397 CALL zgels(
'No transpose', m, n, nrhs, af,
398 $ lda, x, lda, work, lwork, info )
403 $
CALL alaerh( path,
'ZGELS', info, 0,
'N',
404 $ m, n, nrhs, -1, nb, imat,
405 $ nfail, nerrs, nout )
407 CALL zget02(
'No transpose', m, n, nrhs, a,
408 $ lda, x, lda, b, lda, rwork,
418 IF( result( i ).GE.thresh )
THEN
419 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
420 $
CALL alahd( nout, path )
421 WRITE( nout, fmt = 9999 )m, n, k, nb, nx,
422 $ imat, i, result( i )
435 CALL alasum( path, nout, nfail, nrun, nerrs )
437 9999
FORMAT(
' M=', i5,
', N=', i5,
', K=', i5,
', NB=', i4,
', NX=',
438 $ 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 zchklq(dotype, nm, mval, nn, nval, nnb, nbval, nxval, nrhs, thresh, tsterr, nmax, a, af, aq, al, ac, b, x, xact, tau, work, rwork, nout)
ZCHKLQ
subroutine zerrlq(path, nunit)
ZERRLQ
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 zlqt01(m, n, a, af, q, l, lda, tau, work, lwork, rwork, result)
ZLQT01
subroutine zlqt02(m, n, k, a, af, q, l, lda, tau, work, lwork, rwork, result)
ZLQT02
subroutine zlqt03(m, n, k, af, c, cc, q, lda, tau, work, lwork, rwork, result)
ZLQT03