174 SUBROUTINE cgqrts( N, M, P, A, AF, Q, R, LDA, TAUA, B, BF, Z, T,
175 $ BWK, LDB, TAUB, WORK, LWORK, RWORK, RESULT )
182 INTEGER LDA, LDB, LWORK, M, P, N
185 REAL RWORK( * ), RESULT( 4 )
186 COMPLEX A( LDA, * ), AF( LDA, * ), R( LDA, * ),
187 $ q( lda, * ), b( ldb, * ), bf( ldb, * ),
188 $ t( ldb, * ), z( ldb, * ), bwk( ldb, * ),
189 $ taua( * ), taub( * ), work( lwork )
196 parameter( zero = 0.0e+0, one = 1.0e+0 )
198 parameter( czero = ( 0.0e+0, 0.0e+0 ),
199 $ cone = ( 1.0e+0, 0.0e+0 ) )
201 parameter( crogue = ( -1.0e+10, 0.0e+0 ) )
205 REAL ANORM, BNORM, ULP, UNFL, RESID
208 REAL SLAMCH, CLANGE, CLANHE
209 EXTERNAL slamch, clange, clanhe
216 INTRINSIC max, min, real
220 ulp = slamch(
'Precision' )
221 unfl = slamch(
'Safe minimum' )
225 CALL clacpy(
'Full', n, m, a, lda, af, lda )
226 CALL clacpy(
'Full', n, p, b, ldb, bf, ldb )
228 anorm = max( clange(
'1', n, m, a, lda, rwork ), unfl )
229 bnorm = max( clange(
'1', n, p, b, ldb, rwork ), unfl )
233 CALL cggqrf( n, m, p, af, lda, taua, bf, ldb, taub, work,
238 CALL claset(
'Full', n, n, crogue, crogue, q, lda )
239 CALL clacpy(
'Lower', n-1, m, af( 2,1 ), lda, q( 2,1 ), lda )
240 CALL cungqr( n, n, min( n, m ), q, lda, taua, work, lwork, info )
244 CALL claset(
'Full', p, p, crogue, crogue, z, ldb )
246 IF( n.GT.0 .AND. n.LT.p )
247 $
CALL clacpy(
'Full', n, p-n, bf, ldb, z( p-n+1, 1 ), ldb )
249 $
CALL clacpy(
'Lower', n-1, n-1, bf( 2, p-n+1 ), ldb,
250 $ z( p-n+2, p-n+1 ), ldb )
253 $
CALL clacpy(
'Lower', p-1, p-1, bf( n-p+2, 1 ), ldb,
256 CALL cungrq( p, p, min( n, p ), z, ldb, taub, work, lwork, info )
260 CALL claset(
'Full', n, m, czero, czero, r, lda )
261 CALL clacpy(
'Upper', n, m, af, lda, r, lda )
265 CALL claset(
'Full', n, p, czero, czero, t, ldb )
267 CALL clacpy(
'Upper', n, n, bf( 1, p-n+1 ), ldb, t( 1, p-n+1 ),
270 CALL clacpy(
'Full', n-p, p, bf, ldb, t, ldb )
271 CALL clacpy(
'Upper', p, p, bf( n-p+1, 1 ), ldb, t( n-p+1, 1 ),
277 CALL cgemm(
'Conjugate transpose',
'No transpose', n, m, n, -cone,
278 $ q, lda, a, lda, cone, r, lda )
282 resid = clange(
'1', n, m, r, lda, rwork )
283 IF( anorm.GT.zero )
THEN
284 result( 1 ) = ( ( resid / real( max(1,m,n) ) ) / anorm ) / ulp
291 CALL cgemm(
'No Transpose',
'No transpose', n, p, p, cone, t, ldb,
292 $ z, ldb, czero, bwk, ldb )
293 CALL cgemm(
'Conjugate transpose',
'No transpose', n, p, n, -cone,
294 $ q, lda, b, ldb, cone, bwk, ldb )
298 resid = clange(
'1', n, p, bwk, ldb, rwork )
299 IF( bnorm.GT.zero )
THEN
300 result( 2 ) = ( ( resid / real( max(1,p,n ) ) )/bnorm ) / ulp
307 CALL claset(
'Full', n, n, czero, cone, r, lda )
308 CALL cherk(
'Upper',
'Conjugate transpose', n, n, -one, q, lda,
313 resid = clanhe(
'1',
'Upper', n, r, lda, rwork )
314 result( 3 ) = ( resid / real( max( 1, n ) ) ) / ulp
318 CALL claset(
'Full', p, p, czero, cone, t, ldb )
319 CALL cherk(
'Upper',
'Conjugate transpose', p, p, -one, z, ldb,
324 resid = clanhe(
'1',
'Upper', p, t, ldb, rwork )
325 result( 4 ) = ( resid / real( max( 1, p ) ) ) / ulp
subroutine cgqrts(n, m, p, a, af, q, r, lda, taua, b, bf, z, t, bwk, ldb, taub, work, lwork, rwork, result)
CGQRTS
subroutine cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
CGEMM
subroutine cggqrf(n, m, p, a, lda, taua, b, ldb, taub, work, lwork, info)
CGGQRF
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 cungqr(m, n, k, a, lda, tau, work, lwork, info)
CUNGQR
subroutine cungrq(m, n, k, a, lda, tau, work, lwork, info)
CUNGRQ