LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ ctzrqf()

subroutine ctzrqf ( integer m,
integer n,
complex, dimension( lda, * ) a,
integer lda,
complex, dimension( * ) tau,
integer info )

CTZRQF

Download CTZRQF + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> This routine is deprecated and has been replaced by routine CTZRZF.
!>
!> CTZRQF reduces the M-by-N ( M<=N ) complex upper trapezoidal matrix A
!> to upper triangular form by means of unitary transformations.
!>
!> The upper trapezoidal matrix A is factored as
!>
!>    A = ( R  0 ) * Z,
!>
!> where Z is an N-by-N unitary matrix and R is an M-by-M upper
!> triangular matrix.
!> 
Parameters
[in]M
!>          M is INTEGER
!>          The number of rows of the matrix A.  M >= 0.
!> 
[in]N
!>          N is INTEGER
!>          The number of columns of the matrix A.  N >= M.
!> 
[in,out]A
!>          A is COMPLEX array, dimension (LDA,N)
!>          On entry, the leading M-by-N upper trapezoidal part of the
!>          array A must contain the matrix to be factorized.
!>          On exit, the leading M-by-M upper triangular part of A
!>          contains the upper triangular matrix R, and elements M+1 to
!>          N of the first M rows of A, with the array TAU, represent the
!>          unitary matrix Z as a product of M elementary reflectors.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,M).
!> 
[out]TAU
!>          TAU is COMPLEX array, dimension (M)
!>          The scalar factors of the elementary reflectors.
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0: successful exit
!>          < 0: if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!>
!>  The  factorization is obtained by Householder's method.  The kth
!>  transformation matrix, Z( k ), whose conjugate transpose is used to
!>  introduce zeros into the (m - k + 1)th row of A, is given in the form
!>
!>     Z( k ) = ( I     0   ),
!>              ( 0  T( k ) )
!>
!>  where
!>
!>     T( k ) = I - tau*u( k )*u( k )**H,   u( k ) = (   1    ),
!>                                                   (   0    )
!>                                                   ( z( k ) )
!>
!>  tau is a scalar and z( k ) is an ( n - m ) element vector.
!>  tau and z( k ) are chosen to annihilate the elements of the kth row
!>  of X.
!>
!>  The scalar tau is returned in the kth element of TAU and the vector
!>  u( k ) in the kth row of A, such that the elements of z( k ) are
!>  in  a( k, m + 1 ), ..., a( k, n ). The elements of R are returned in
!>  the upper triangular part of A.
!>
!>  Z is given by
!>
!>     Z =  Z( 1 ) * Z( 2 ) * ... * Z( m ).
!> 

Definition at line 135 of file ctzrqf.f.

136*
137* -- LAPACK computational routine --
138* -- LAPACK is a software package provided by Univ. of Tennessee, --
139* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
140*
141* .. Scalar Arguments ..
142 INTEGER INFO, LDA, M, N
143* ..
144* .. Array Arguments ..
145 COMPLEX A( LDA, * ), TAU( * )
146* ..
147*
148* =====================================================================
149*
150* .. Parameters ..
151 COMPLEX CONE, CZERO
152 parameter( cone = ( 1.0e+0, 0.0e+0 ),
153 $ czero = ( 0.0e+0, 0.0e+0 ) )
154* ..
155* .. Local Scalars ..
156 INTEGER I, K, M1
157 COMPLEX ALPHA
158* ..
159* .. Intrinsic Functions ..
160 INTRINSIC conjg, max, min
161* ..
162* .. External Subroutines ..
163 EXTERNAL caxpy, ccopy, cgemv, cgerc, clacgv, clarfg,
164 $ xerbla
165* ..
166* .. Executable Statements ..
167*
168* Test the input parameters.
169*
170 info = 0
171 IF( m.LT.0 ) THEN
172 info = -1
173 ELSE IF( n.LT.m ) THEN
174 info = -2
175 ELSE IF( lda.LT.max( 1, m ) ) THEN
176 info = -4
177 END IF
178 IF( info.NE.0 ) THEN
179 CALL xerbla( 'CTZRQF', -info )
180 RETURN
181 END IF
182*
183* Perform the factorization.
184*
185 IF( m.EQ.0 )
186 $ RETURN
187 IF( m.EQ.n ) THEN
188 DO 10 i = 1, n
189 tau( i ) = czero
190 10 CONTINUE
191 ELSE
192 m1 = min( m+1, n )
193 DO 20 k = m, 1, -1
194*
195* Use a Householder reflection to zero the kth row of A.
196* First set up the reflection.
197*
198 a( k, k ) = conjg( a( k, k ) )
199 CALL clacgv( n-m, a( k, m1 ), lda )
200 alpha = a( k, k )
201 CALL clarfg( n-m+1, alpha, a( k, m1 ), lda, tau( k ) )
202 a( k, k ) = alpha
203 tau( k ) = conjg( tau( k ) )
204*
205 IF( tau( k ).NE.czero .AND. k.GT.1 ) THEN
206*
207* We now perform the operation A := A*P( k )**H.
208*
209* Use the first ( k - 1 ) elements of TAU to store a( k ),
210* where a( k ) consists of the first ( k - 1 ) elements of
211* the kth column of A. Also let B denote the first
212* ( k - 1 ) rows of the last ( n - m ) columns of A.
213*
214 CALL ccopy( k-1, a( 1, k ), 1, tau, 1 )
215*
216* Form w = a( k ) + B*z( k ) in TAU.
217*
218 CALL cgemv( 'No transpose', k-1, n-m, cone,
219 $ a( 1, m1 ), lda, a( k, m1 ), lda, cone,
220 $ tau, 1 )
221*
222* Now form a( k ) := a( k ) - conjg(tau)*w
223* and B := B - conjg(tau)*w*z( k )**H.
224*
225 CALL caxpy( k-1, -conjg( tau( k ) ), tau, 1,
226 $ a( 1, k ), 1 )
227 CALL cgerc( k-1, n-m, -conjg( tau( k ) ), tau, 1,
228 $ a( k, m1 ), lda, a( 1, m1 ), lda )
229 END IF
230 20 CONTINUE
231 END IF
232*
233 RETURN
234*
235* End of CTZRQF
236*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine caxpy(n, ca, cx, incx, cy, incy)
CAXPY
Definition caxpy.f:88
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
Definition ccopy.f:81
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV
Definition cgemv.f:160
subroutine cgerc(m, n, alpha, x, incx, y, incy, a, lda)
CGERC
Definition cgerc.f:130
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
Definition clacgv.f:72
subroutine clarfg(n, alpha, x, incx, tau)
CLARFG generates an elementary reflector (Householder matrix).
Definition clarfg.f:104
Here is the call graph for this function:
Here is the caller graph for this function: