124 SUBROUTINE clqt01( M, N, A, AF, Q, L, LDA, TAU, WORK, LWORK,
132 INTEGER LDA, LWORK, M, N
135 REAL RESULT( * ), RWORK( * )
136 COMPLEX A( LDA, * ), AF( LDA, * ), L( LDA, * ),
137 $ q( lda, * ), tau( * ), work( lwork )
144 parameter( zero = 0.0e+0, one = 1.0e+0 )
146 parameter( rogue = ( -1.0e+10, -1.0e+10 ) )
150 REAL ANORM, EPS, RESID
153 REAL CLANGE, CLANSY, SLAMCH
154 EXTERNAL clange, clansy, slamch
160 INTRINSIC cmplx, max, min, real
166 COMMON / srnamc / srnamt
171 eps = slamch(
'Epsilon' )
175 CALL clacpy(
'Full', m, n, a, lda, af, lda )
180 CALL cgelqf( m, n, af, lda, tau, work, lwork, info )
184 CALL claset(
'Full', n, n, rogue, rogue, q, lda )
186 $
CALL clacpy(
'Upper', m, n-1, af( 1, 2 ), lda, q( 1, 2 ), lda )
191 CALL cunglq( n, n, minmn, q, lda, tau, work, lwork, info )
195 CALL claset(
'Full', m, n, cmplx( zero ), cmplx( zero ), l, lda )
196 CALL clacpy(
'Lower', m, n, af, lda, l, lda )
200 CALL cgemm(
'No transpose',
'Conjugate transpose', m, n, n,
201 $ cmplx( -one ), a, lda, q, lda, cmplx( one ), l, lda )
205 anorm = clange(
'1', m, n, a, lda, rwork )
206 resid = clange(
'1', m, n, l, lda, rwork )
207 IF( anorm.GT.zero )
THEN
208 result( 1 ) = ( ( resid / real( max( 1, n ) ) ) / anorm ) / eps
215 CALL claset(
'Full', n, n, cmplx( zero ), cmplx( one ), l, lda )
216 CALL cherk(
'Upper',
'No transpose', n, n, -one, q, lda, one, l,
221 resid = clansy(
'1',
'Upper', n, l, lda, rwork )
223 result( 2 ) = ( resid / real( max( 1, n ) ) ) / eps
subroutine clqt01(m, n, a, af, q, l, lda, tau, work, lwork, rwork, result)
CLQT01
subroutine cgelqf(m, n, a, lda, tau, work, lwork, info)
CGELQF
subroutine cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
CGEMM
subroutine cherk(uplo, trans, n, k, alpha, a, lda, beta, c, ldc)
CHERK
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 cunglq(m, n, k, a, lda, tau, work, lwork, info)
CUNGLQ