LAPACK 3.3.0

cgelq2.f

Go to the documentation of this file.
00001       SUBROUTINE CGELQ2( M, N, A, LDA, TAU, WORK, 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       COMPLEX            A( LDA, * ), TAU( * ), WORK( * )
00013 *     ..
00014 *
00015 *  Purpose
00016 *  =======
00017 *
00018 *  CGELQ2 computes an LQ factorization of a complex m by n matrix A:
00019 *  A = L * Q.
00020 *
00021 *  Arguments
00022 *  =========
00023 *
00024 *  M       (input) INTEGER
00025 *          The number of rows of the matrix A.  M >= 0.
00026 *
00027 *  N       (input) INTEGER
00028 *          The number of columns of the matrix A.  N >= 0.
00029 *
00030 *  A       (input/output) COMPLEX array, dimension (LDA,N)
00031 *          On entry, the m by n matrix A.
00032 *          On exit, the elements on and below the diagonal of the array
00033 *          contain the m by min(m,n) lower trapezoidal matrix L (L is
00034 *          lower triangular if m <= n); the elements above the diagonal,
00035 *          with the array TAU, represent the unitary matrix Q as a
00036 *          product of elementary reflectors (see Further Details).
00037 *
00038 *  LDA     (input) INTEGER
00039 *          The leading dimension of the array A.  LDA >= max(1,M).
00040 *
00041 *  TAU     (output) COMPLEX array, dimension (min(M,N))
00042 *          The scalar factors of the elementary reflectors (see Further
00043 *          Details).
00044 *
00045 *  WORK    (workspace) COMPLEX array, dimension (M)
00046 *
00047 *  INFO    (output) INTEGER
00048 *          = 0: successful exit
00049 *          < 0: if INFO = -i, the i-th argument had an illegal value
00050 *
00051 *  Further Details
00052 *  ===============
00053 *
00054 *  The matrix Q is represented as a product of elementary reflectors
00055 *
00056 *     Q = H(k)' . . . H(2)' H(1)', where k = min(m,n).
00057 *
00058 *  Each H(i) has the form
00059 *
00060 *     H(i) = I - tau * v * v'
00061 *
00062 *  where tau is a complex scalar, and v is a complex vector with
00063 *  v(1:i-1) = 0 and v(i) = 1; conjg(v(i+1:n)) is stored on exit in
00064 *  A(i,i+1:n), and tau in TAU(i).
00065 *
00066 *  =====================================================================
00067 *
00068 *     .. Parameters ..
00069       COMPLEX            ONE
00070       PARAMETER          ( ONE = ( 1.0E+0, 0.0E+0 ) )
00071 *     ..
00072 *     .. Local Scalars ..
00073       INTEGER            I, K
00074       COMPLEX            ALPHA
00075 *     ..
00076 *     .. External Subroutines ..
00077       EXTERNAL           CLACGV, CLARF, CLARFG, XERBLA
00078 *     ..
00079 *     .. Intrinsic Functions ..
00080       INTRINSIC          MAX, MIN
00081 *     ..
00082 *     .. Executable Statements ..
00083 *
00084 *     Test the input arguments
00085 *
00086       INFO = 0
00087       IF( M.LT.0 ) THEN
00088          INFO = -1
00089       ELSE IF( N.LT.0 ) THEN
00090          INFO = -2
00091       ELSE IF( LDA.LT.MAX( 1, M ) ) THEN
00092          INFO = -4
00093       END IF
00094       IF( INFO.NE.0 ) THEN
00095          CALL XERBLA( 'CGELQ2', -INFO )
00096          RETURN
00097       END IF
00098 *
00099       K = MIN( M, N )
00100 *
00101       DO 10 I = 1, K
00102 *
00103 *        Generate elementary reflector H(i) to annihilate A(i,i+1:n)
00104 *
00105          CALL CLACGV( N-I+1, A( I, I ), LDA )
00106          ALPHA = A( I, I )
00107          CALL CLARFG( N-I+1, ALPHA, A( I, MIN( I+1, N ) ), LDA,
00108      $                TAU( I ) )
00109          IF( I.LT.M ) THEN
00110 *
00111 *           Apply H(i) to A(i+1:m,i:n) from the right
00112 *
00113             A( I, I ) = ONE
00114             CALL CLARF( 'Right', M-I, N-I+1, A( I, I ), LDA, TAU( I ),
00115      $                  A( I+1, I ), LDA, WORK )
00116          END IF
00117          A( I, I ) = ALPHA
00118          CALL CLACGV( N-I+1, A( I, I ), LDA )
00119    10 CONTINUE
00120       RETURN
00121 *
00122 *     End of CGELQ2
00123 *
00124       END
 All Files Functions