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

◆ stzrqf()

subroutine stzrqf ( integer  m,
integer  n,
real, dimension( lda, * )  a,
integer  lda,
real, dimension( * )  tau,
integer  info 
)

STZRQF

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

Purpose:
 This routine is deprecated and has been replaced by routine STZRZF.

 STZRQF reduces the M-by-N ( M<=N ) real upper trapezoidal matrix A
 to upper triangular form by means of orthogonal transformations.

 The upper trapezoidal matrix A is factored as

    A = ( R  0 ) * Z,

 where Z is an N-by-N orthogonal 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 REAL 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
          orthogonal 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 REAL 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 ), which 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 )**T,   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 137 of file stzrqf.f.

138*
139* -- LAPACK computational routine --
140* -- LAPACK is a software package provided by Univ. of Tennessee, --
141* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
142*
143* .. Scalar Arguments ..
144 INTEGER INFO, LDA, M, N
145* ..
146* .. Array Arguments ..
147 REAL A( LDA, * ), TAU( * )
148* ..
149*
150* =====================================================================
151*
152* .. Parameters ..
153 REAL ONE, ZERO
154 parameter( one = 1.0e+0, zero = 0.0e+0 )
155* ..
156* .. Local Scalars ..
157 INTEGER I, K, M1
158* ..
159* .. Intrinsic Functions ..
160 INTRINSIC max, min
161* ..
162* .. External Subroutines ..
163 EXTERNAL saxpy, scopy, sgemv, sger, slarfg, xerbla
164* ..
165* .. Executable Statements ..
166*
167* Test the input parameters.
168*
169 info = 0
170 IF( m.LT.0 ) THEN
171 info = -1
172 ELSE IF( n.LT.m ) THEN
173 info = -2
174 ELSE IF( lda.LT.max( 1, m ) ) THEN
175 info = -4
176 END IF
177 IF( info.NE.0 ) THEN
178 CALL xerbla( 'STZRQF', -info )
179 RETURN
180 END IF
181*
182* Perform the factorization.
183*
184 IF( m.EQ.0 )
185 $ RETURN
186 IF( m.EQ.n ) THEN
187 DO 10 i = 1, n
188 tau( i ) = zero
189 10 CONTINUE
190 ELSE
191 m1 = min( m+1, n )
192 DO 20 k = m, 1, -1
193*
194* Use a Householder reflection to zero the kth row of A.
195* First set up the reflection.
196*
197 CALL slarfg( n-m+1, a( k, k ), a( k, m1 ), lda, tau( k ) )
198*
199 IF( ( tau( k ).NE.zero ) .AND. ( k.GT.1 ) ) THEN
200*
201* We now perform the operation A := A*P( k ).
202*
203* Use the first ( k - 1 ) elements of TAU to store a( k ),
204* where a( k ) consists of the first ( k - 1 ) elements of
205* the kth column of A. Also let B denote the first
206* ( k - 1 ) rows of the last ( n - m ) columns of A.
207*
208 CALL scopy( k-1, a( 1, k ), 1, tau, 1 )
209*
210* Form w = a( k ) + B*z( k ) in TAU.
211*
212 CALL sgemv( 'No transpose', k-1, n-m, one, a( 1, m1 ),
213 $ lda, a( k, m1 ), lda, one, tau, 1 )
214*
215* Now form a( k ) := a( k ) - tau*w
216* and B := B - tau*w*z( k )**T.
217*
218 CALL saxpy( k-1, -tau( k ), tau, 1, a( 1, k ), 1 )
219 CALL sger( k-1, n-m, -tau( k ), tau, 1, a( k, m1 ), lda,
220 $ a( 1, m1 ), lda )
221 END IF
222 20 CONTINUE
223 END IF
224*
225 RETURN
226*
227* End of STZRQF
228*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine saxpy(n, sa, sx, incx, sy, incy)
SAXPY
Definition saxpy.f:89
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
Definition scopy.f:82
subroutine sgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
SGEMV
Definition sgemv.f:158
subroutine sger(m, n, alpha, x, incx, y, incy, a, lda)
SGER
Definition sger.f:130
subroutine slarfg(n, alpha, x, incx, tau)
SLARFG generates an elementary reflector (Householder matrix).
Definition slarfg.f:106
Here is the call graph for this function:
Here is the caller graph for this function: