131 RECURSIVE SUBROUTINE cgeqrt3( M, N, A, LDA, T, LDT, INFO )
138 INTEGER info, lda, m, n, ldt
141 COMPLEX a( lda, * ), t( ldt, * )
148 parameter( one = (1.0,0.0) )
151 INTEGER i, i1, j, j1, n1, n2, iinfo
161 ELSE IF( m .LT. n )
THEN
163 ELSE IF( lda .LT. max( 1, m ) )
THEN
165 ELSE IF( ldt .LT. max( 1, n ) )
THEN
169 CALL xerbla(
'CGEQRT3', -info )
177 CALL clarfg( m, a(1,1), a( min( 2, m ), 1 ), 1, t(1,1) )
190 CALL cgeqrt3( m, n1, a, lda, t, ldt, iinfo )
196 t( i, j+n1 ) = a( i, j+n1 )
199 CALL ctrmm(
'L',
'L',
'C',
'U', n1, n2, one,
200 & a, lda, t( 1, j1 ), ldt )
202 CALL cgemm(
'C',
'N', n1, n2, m-n1, one, a( j1, 1 ), lda,
203 & a( j1, j1 ), lda, one, t( 1, j1 ), ldt)
205 CALL ctrmm(
'L',
'U',
'C',
'N', n1, n2, one,
206 & t, ldt, t( 1, j1 ), ldt )
208 CALL cgemm(
'N',
'N', m-n1, n2, n1, -one, a( j1, 1 ), lda,
209 & t( 1, j1 ), ldt, one, a( j1, j1 ), lda )
211 CALL ctrmm(
'L',
'L',
'N',
'U', n1, n2, one,
212 & a, lda, t( 1, j1 ), ldt )
216 a( i, j+n1 ) = a( i, j+n1 ) - t( i, j+n1 )
222 CALL cgeqrt3( m-n1, n2, a( j1, j1 ), lda,
223 & t( j1, j1 ), ldt, iinfo )
229 t( i, j+n1 ) = conjg(a( j+n1, i ))
233 CALL ctrmm(
'R',
'L',
'N',
'U', n1, n2, one,
234 & a( j1, j1 ), lda, t( 1, j1 ), ldt )
236 CALL cgemm(
'C',
'N', n1, n2, m-n, one, a( i1, 1 ), lda,
237 & a( i1, j1 ), lda, one, t( 1, j1 ), ldt )
239 CALL ctrmm(
'L',
'U',
'N',
'N', n1, n2, -one, t, ldt,
242 CALL ctrmm(
'R',
'U',
'N',
'N', n1, n2, one,
243 & t( j1, j1 ), ldt, t( 1, j1 ), ldt )
subroutine xerbla(srname, info)
subroutine cgemm(transa, transb, m, n, k, alpha, a, lda, b, ldb, beta, c, ldc)
CGEMM
recursive subroutine cgeqrt3(m, n, a, lda, t, ldt, info)
CGEQRT3 recursively computes a QR factorization of a general real or complex matrix using the compact...
subroutine clarfg(n, alpha, x, incx, tau)
CLARFG generates an elementary reflector (Householder matrix).
subroutine ctrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
CTRMM