LAPACK 3.3.0

dtzrqf.f

Go to the documentation of this file.
00001       SUBROUTINE DTZRQF( M, N, A, LDA, TAU, INFO )
00002 *
00003 *  -- LAPACK routine (version 3.2.2) --
00004 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
00005 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
00006 *     June 2010
00007 *
00008 *     .. Scalar Arguments ..
00009       INTEGER            INFO, LDA, M, N
00010 *     ..
00011 *     .. Array Arguments ..
00012       DOUBLE PRECISION   A( LDA, * ), TAU( * )
00013 *     ..
00014 *
00015 *  Purpose
00016 *  =======
00017 *
00018 *  This routine is deprecated and has been replaced by routine DTZRZF.
00019 *
00020 *  DTZRQF reduces the M-by-N ( M<=N ) real upper trapezoidal matrix A
00021 *  to upper triangular form by means of orthogonal transformations.
00022 *
00023 *  The upper trapezoidal matrix A is factored as
00024 *
00025 *     A = ( R  0 ) * Z,
00026 *
00027 *  where Z is an N-by-N orthogonal matrix and R is an M-by-M upper
00028 *  triangular matrix.
00029 *
00030 *  Arguments
00031 *  =========
00032 *
00033 *  M       (input) INTEGER
00034 *          The number of rows of the matrix A.  M >= 0.
00035 *
00036 *  N       (input) INTEGER
00037 *          The number of columns of the matrix A.  N >= M.
00038 *
00039 *  A       (input/output) DOUBLE PRECISION array, dimension (LDA,N)
00040 *          On entry, the leading M-by-N upper trapezoidal part of the
00041 *          array A must contain the matrix to be factorized.
00042 *          On exit, the leading M-by-M upper triangular part of A
00043 *          contains the upper triangular matrix R, and elements M+1 to
00044 *          N of the first M rows of A, with the array TAU, represent the
00045 *          orthogonal matrix Z as a product of M elementary reflectors.
00046 *
00047 *  LDA     (input) INTEGER
00048 *          The leading dimension of the array A.  LDA >= max(1,M).
00049 *
00050 *  TAU     (output) DOUBLE PRECISION array, dimension (M)
00051 *          The scalar factors of the elementary reflectors.
00052 *
00053 *  INFO    (output) INTEGER
00054 *          = 0:  successful exit
00055 *          < 0:  if INFO = -i, the i-th argument had an illegal value
00056 *
00057 *  Further Details
00058 *  ===============
00059 *
00060 *  The factorization is obtained by Householder's method.  The kth
00061 *  transformation matrix, Z( k ), which is used to introduce zeros into
00062 *  the ( m - k + 1 )th row of A, is given in the form
00063 *
00064 *     Z( k ) = ( I     0   ),
00065 *              ( 0  T( k ) )
00066 *
00067 *  where
00068 *
00069 *     T( k ) = I - tau*u( k )*u( k )',   u( k ) = (   1    ),
00070 *                                                 (   0    )
00071 *                                                 ( z( k ) )
00072 *
00073 *  tau is a scalar and z( k ) is an ( n - m ) element vector.
00074 *  tau and z( k ) are chosen to annihilate the elements of the kth row
00075 *  of X.
00076 *
00077 *  The scalar tau is returned in the kth element of TAU and the vector
00078 *  u( k ) in the kth row of A, such that the elements of z( k ) are
00079 *  in  a( k, m + 1 ), ..., a( k, n ). The elements of R are returned in
00080 *  the upper triangular part of A.
00081 *
00082 *  Z is given by
00083 *
00084 *     Z =  Z( 1 ) * Z( 2 ) * ... * Z( m ).
00085 *
00086 *  =====================================================================
00087 *
00088 *     .. Parameters ..
00089       DOUBLE PRECISION   ONE, ZERO
00090       PARAMETER          ( ONE = 1.0D+0, ZERO = 0.0D+0 )
00091 *     ..
00092 *     .. Local Scalars ..
00093       INTEGER            I, K, M1
00094 *     ..
00095 *     .. Intrinsic Functions ..
00096       INTRINSIC          MAX, MIN
00097 *     ..
00098 *     .. External Subroutines ..
00099       EXTERNAL           DAXPY, DCOPY, DGEMV, DGER, DLARFG, XERBLA
00100 *     ..
00101 *     .. Executable Statements ..
00102 *
00103 *     Test the input parameters.
00104 *
00105       INFO = 0
00106       IF( M.LT.0 ) THEN
00107          INFO = -1
00108       ELSE IF( N.LT.M ) THEN
00109          INFO = -2
00110       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
00111          INFO = -4
00112       END IF
00113       IF( INFO.NE.0 ) THEN
00114          CALL XERBLA( 'DTZRQF', -INFO )
00115          RETURN
00116       END IF
00117 *
00118 *     Perform the factorization.
00119 *
00120       IF( M.EQ.0 )
00121      $   RETURN
00122       IF( M.EQ.N ) THEN
00123          DO 10 I = 1, N
00124             TAU( I ) = ZERO
00125    10    CONTINUE
00126       ELSE
00127          M1 = MIN( M+1, N )
00128          DO 20 K = M, 1, -1
00129 *
00130 *           Use a Householder reflection to zero the kth row of A.
00131 *           First set up the reflection.
00132 *
00133             CALL DLARFG( N-M+1, A( K, K ), A( K, M1 ), LDA, TAU( K ) )
00134 *
00135             IF( ( TAU( K ).NE.ZERO ) .AND. ( K.GT.1 ) ) THEN
00136 *
00137 *              We now perform the operation  A := A*P( k ).
00138 *
00139 *              Use the first ( k - 1 ) elements of TAU to store  a( k ),
00140 *              where  a( k ) consists of the first ( k - 1 ) elements of
00141 *              the  kth column  of  A.  Also  let  B  denote  the  first
00142 *              ( k - 1 ) rows of the last ( n - m ) columns of A.
00143 *
00144                CALL DCOPY( K-1, A( 1, K ), 1, TAU, 1 )
00145 *
00146 *              Form   w = a( k ) + B*z( k )  in TAU.
00147 *
00148                CALL DGEMV( 'No transpose', K-1, N-M, ONE, A( 1, M1 ),
00149      $                     LDA, A( K, M1 ), LDA, ONE, TAU, 1 )
00150 *
00151 *              Now form  a( k ) := a( k ) - tau*w
00152 *              and       B      := B      - tau*w*z( k )'.
00153 *
00154                CALL DAXPY( K-1, -TAU( K ), TAU, 1, A( 1, K ), 1 )
00155                CALL DGER( K-1, N-M, -TAU( K ), TAU, 1, A( K, M1 ), LDA,
00156      $                    A( 1, M1 ), LDA )
00157             END IF
00158    20    CONTINUE
00159       END IF
00160 *
00161       RETURN
00162 *
00163 *     End of DTZRQF
00164 *
00165       END
 All Files Functions