Annotation of rpl/lapack/lapack/zlapll.f, revision 1.1

1.1     ! bertrand    1:       SUBROUTINE ZLAPLL( N, X, INCX, Y, INCY, SSMIN )
        !             2: *
        !             3: *  -- LAPACK auxiliary routine (version 3.2) --
        !             4: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
        !             5: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
        !             6: *     November 2006
        !             7: *
        !             8: *     .. Scalar Arguments ..
        !             9:       INTEGER            INCX, INCY, N
        !            10:       DOUBLE PRECISION   SSMIN
        !            11: *     ..
        !            12: *     .. Array Arguments ..
        !            13:       COMPLEX*16         X( * ), Y( * )
        !            14: *     ..
        !            15: *
        !            16: *  Purpose
        !            17: *  =======
        !            18: *
        !            19: *  Given two column vectors X and Y, let
        !            20: *
        !            21: *                       A = ( X Y ).
        !            22: *
        !            23: *  The subroutine first computes the QR factorization of A = Q*R,
        !            24: *  and then computes the SVD of the 2-by-2 upper triangular matrix R.
        !            25: *  The smaller singular value of R is returned in SSMIN, which is used
        !            26: *  as the measurement of the linear dependency of the vectors X and Y.
        !            27: *
        !            28: *  Arguments
        !            29: *  =========
        !            30: *
        !            31: *  N       (input) INTEGER
        !            32: *          The length of the vectors X and Y.
        !            33: *
        !            34: *  X       (input/output) COMPLEX*16 array, dimension (1+(N-1)*INCX)
        !            35: *          On entry, X contains the N-vector X.
        !            36: *          On exit, X is overwritten.
        !            37: *
        !            38: *  INCX    (input) INTEGER
        !            39: *          The increment between successive elements of X. INCX > 0.
        !            40: *
        !            41: *  Y       (input/output) COMPLEX*16 array, dimension (1+(N-1)*INCY)
        !            42: *          On entry, Y contains the N-vector Y.
        !            43: *          On exit, Y is overwritten.
        !            44: *
        !            45: *  INCY    (input) INTEGER
        !            46: *          The increment between successive elements of Y. INCY > 0.
        !            47: *
        !            48: *  SSMIN   (output) DOUBLE PRECISION
        !            49: *          The smallest singular value of the N-by-2 matrix A = ( X Y ).
        !            50: *
        !            51: *  =====================================================================
        !            52: *
        !            53: *     .. Parameters ..
        !            54:       DOUBLE PRECISION   ZERO
        !            55:       PARAMETER          ( ZERO = 0.0D+0 )
        !            56:       COMPLEX*16         CONE
        !            57:       PARAMETER          ( CONE = ( 1.0D+0, 0.0D+0 ) )
        !            58: *     ..
        !            59: *     .. Local Scalars ..
        !            60:       DOUBLE PRECISION   SSMAX
        !            61:       COMPLEX*16         A11, A12, A22, C, TAU
        !            62: *     ..
        !            63: *     .. Intrinsic Functions ..
        !            64:       INTRINSIC          ABS, DCONJG
        !            65: *     ..
        !            66: *     .. External Functions ..
        !            67:       COMPLEX*16         ZDOTC
        !            68:       EXTERNAL           ZDOTC
        !            69: *     ..
        !            70: *     .. External Subroutines ..
        !            71:       EXTERNAL           DLAS2, ZAXPY, ZLARFG
        !            72: *     ..
        !            73: *     .. Executable Statements ..
        !            74: *
        !            75: *     Quick return if possible
        !            76: *
        !            77:       IF( N.LE.1 ) THEN
        !            78:          SSMIN = ZERO
        !            79:          RETURN
        !            80:       END IF
        !            81: *
        !            82: *     Compute the QR factorization of the N-by-2 matrix ( X Y )
        !            83: *
        !            84:       CALL ZLARFG( N, X( 1 ), X( 1+INCX ), INCX, TAU )
        !            85:       A11 = X( 1 )
        !            86:       X( 1 ) = CONE
        !            87: *
        !            88:       C = -DCONJG( TAU )*ZDOTC( N, X, INCX, Y, INCY )
        !            89:       CALL ZAXPY( N, C, X, INCX, Y, INCY )
        !            90: *
        !            91:       CALL ZLARFG( N-1, Y( 1+INCY ), Y( 1+2*INCY ), INCY, TAU )
        !            92: *
        !            93:       A12 = Y( 1 )
        !            94:       A22 = Y( 1+INCY )
        !            95: *
        !            96: *     Compute the SVD of 2-by-2 Upper triangular matrix.
        !            97: *
        !            98:       CALL DLAS2( ABS( A11 ), ABS( A12 ), ABS( A22 ), SSMIN, SSMAX )
        !            99: *
        !           100:       RETURN
        !           101: *
        !           102: *     End of ZLAPLL
        !           103: *
        !           104:       END

CVSweb interface <joel.bertrand@systella.fr>