LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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.
Date
November 2011
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 140 of file stzrqf.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: