174 SUBROUTINE cgrqts( M, P, N, 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 RESULT( 4 ), RWORK( * )
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', m, n, a, lda, af, lda )
226 CALL clacpy(
'Full', p, n, b, ldb, bf, ldb )
228 anorm = max( clange(
'1', m, n, a, lda, rwork ), unfl )
229 bnorm = max( clange(
'1', p, n, b, ldb, rwork ), unfl )
233 CALL cggrqf( m, p, n, af, lda, taua, bf, ldb, taub, work,
238 CALL claset(
'Full', n, n, crogue, crogue, q, lda )
240 IF( m.GT.0 .AND. m.LT.n )
241 $
CALL clacpy(
'Full', m, n-m, af, lda, q( n-m+1, 1 ), lda )
243 $
CALL clacpy(
'Lower', m-1, m-1, af( 2, n-m+1 ), lda,
244 $ q( n-m+2, n-m+1 ), lda )
247 $
CALL clacpy(
'Lower', n-1, n-1, af( m-n+2, 1 ), lda,
250 CALL cungrq( n, n, min( m, n ), q, lda, taua, work, lwork, info )
254 CALL claset(
'Full', p, p, crogue, crogue, z, ldb )
256 $
CALL clacpy(
'Lower', p-1, n, bf( 2,1 ), ldb, z( 2,1 ), ldb )
257 CALL cungqr( p, p, min( p,n ), z, ldb, taub, work, lwork, info )
261 CALL claset(
'Full', m, n, czero, czero, r, lda )
263 CALL clacpy(
'Upper', m, m, af( 1, n-m+1 ), lda, r( 1, n-m+1 ),
266 CALL clacpy(
'Full', m-n, n, af, lda, r, lda )
267 CALL clacpy(
'Upper', n, n, af( m-n+1, 1 ), lda, r( m-n+1, 1 ),
273 CALL claset(
'Full', p, n, czero, czero, t, ldb )
274 CALL clacpy(
'Upper', p, n, bf, ldb, t, ldb )
278 CALL cgemm(
'No transpose',
'Conjugate transpose', m, n, n, -cone,
279 $ a, lda, q, lda, cone, r, lda )
283 resid = clange(
'1', m, n, r, lda, rwork )
284 IF( anorm.GT.zero )
THEN
285 result( 1 ) = ( ( resid / real(max(1,m,n) ) ) / anorm ) / ulp
292 CALL cgemm(
'Conjugate transpose',
'No transpose', p, n, p, cone,
293 $ z, ldb, b, ldb, czero, bwk, ldb )
294 CALL cgemm(
'No transpose',
'No transpose', p, n, n, cone, t, ldb,
295 $ q, lda, -cone, bwk, ldb )
299 resid = clange(
'1', p, n, bwk, ldb, rwork )
300 IF( bnorm.GT.zero )
THEN
301 result( 2 ) = ( ( resid / real( max( 1,p,m ) ) )/bnorm ) / ulp
308 CALL claset(
'Full', n, n, czero, cone, r, lda )
309 CALL cherk(
'Upper',
'No Transpose', n, n, -one, q, lda, one, r,
314 resid = clanhe(
'1',
'Upper', n, r, lda, rwork )
315 result( 3 ) = ( resid / real( max( 1,n ) ) ) / ulp
319 CALL claset(
'Full', p, p, czero, cone, t, ldb )
320 CALL cherk(
'Upper',
'Conjugate transpose', p, p, -one, z, ldb,
325 resid = clanhe(
'1',
'Upper', p, t, ldb, rwork )
326 result( 4 ) = ( resid / real( max( 1,p ) ) ) / ulp