135 SUBROUTINE cchktz( DOTYPE, NM, MVAL, NN, NVAL, THRESH, TSTERR, A,
136 $ COPYA, S, TAU, WORK, RWORK, NOUT )
149 INTEGER MVAL( * ), NVAL( * )
150 REAL S( * ), RWORK( * )
151 COMPLEX A( * ), COPYA( * ), TAU( * ), WORK( * )
158 parameter( ntypes = 3 )
160 parameter( ntests = 3 )
162 parameter( one = 1.0e0, zero = 0.0e0 )
166 INTEGER I, IM, IMODE, IN, INFO, K, LDA, LWORK, M,
167 $ mnmin, mode, n, nerrs, nfail, nrun
171 INTEGER ISEED( 4 ), ISEEDY( 4 )
172 REAL RESULT( NTESTS )
175 REAL CQRT12, CRZT01, CRZT02, SLAMCH
176 EXTERNAL cqrt12, crzt01, crzt02, slamch
183 INTRINSIC cmplx, max, min
188 INTEGER INFOT, IOUNIT
191 COMMON / infoc / infot, iounit, ok, lerr
192 COMMON / srnamc / srnamt
195 DATA iseedy / 1988, 1989, 1990, 1991 /
201 path( 1: 1 ) =
'Complex precision'
207 iseed( i ) = iseedy( i )
209 eps = slamch(
'Epsilon' )
214 $
CALL cerrtz( path, nout )
230 lwork = max( 1, n*n+4*m+n )
233 DO 50 imode = 1, ntypes
234 IF( .NOT.dotype( imode ) )
250 CALL claset(
'Full', m, n, cmplx( zero ),
251 $ cmplx( zero ), a, lda )
256 CALL clatms( m, n,
'Uniform', iseed,
257 $
'Nonsymmetric', s, imode,
258 $ one / eps, one, m, n,
'No packing', a,
260 CALL cgeqr2( m, n, a, lda, work, work( mnmin+1 ),
262 CALL claset(
'Lower', m-1, n, cmplx( zero ),
263 $ cmplx( zero ), a( 2 ), lda )
264 CALL slaord(
'Decreasing', mnmin, s, 1 )
269 CALL clacpy(
'All', m, n, a, lda, copya, lda )
275 CALL ctzrzf( m, n, a, lda, tau, work, lwork, info )
279 result( 1 ) = cqrt12( m, m, a, lda, s, work,
284 result( 2 ) = crzt01( m, n, copya, a, lda, tau, work,
289 result( 3 ) = crzt02( m, n, a, lda, tau, work, lwork )
295 IF( result( k ).GE.thresh )
THEN
296 IF( nfail.EQ.0 .AND. nerrs.EQ.0 )
297 $
CALL alahd( nout, path )
298 WRITE( nout, fmt = 9999 )m, n, imode, k,
311 CALL alasum( path, nout, nfail, nrun, nerrs )
313 9999
FORMAT(
' M =', i5,
', N =', i5,
', type ', i2,
', test ', i2,
314 $
', ratio =', g12.5 )
subroutine alasum(type, nout, nfail, nrun, nerrs)
ALASUM
subroutine alahd(iounit, path)
ALAHD
subroutine cchktz(dotype, nm, mval, nn, nval, thresh, tsterr, a, copya, s, tau, work, rwork, nout)
CCHKTZ
subroutine cerrtz(path, nunit)
CERRTZ
subroutine clatms(m, n, dist, iseed, sym, d, mode, cond, dmax, kl, ku, pack, a, lda, work, info)
CLATMS
subroutine cgeqr2(m, n, a, lda, tau, work, info)
CGEQR2 computes the QR factorization of a general rectangular matrix using an unblocked algorithm.
subroutine clacpy(uplo, m, n, a, lda, b, ldb)
CLACPY copies all or part of one two-dimensional array to another.
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
subroutine ctzrzf(m, n, a, lda, tau, work, lwork, info)
CTZRZF
subroutine slaord(job, n, x, incx)
SLAORD