001:       SUBROUTINE CLAPLL( N, X, INCX, Y, INCY, SSMIN )
002: *
003: *  -- LAPACK auxiliary routine (version 3.2) --
004: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
005: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
006: *     November 2006
007: *
008: *     .. Scalar Arguments ..
009:       INTEGER            INCX, INCY, N
010:       REAL               SSMIN
011: *     ..
012: *     .. Array Arguments ..
013:       COMPLEX            X( * ), Y( * )
014: *     ..
015: *
016: *  Purpose
017: *  =======
018: *
019: *  Given two column vectors X and Y, let
020: *
021: *                       A = ( X Y ).
022: *
023: *  The subroutine first computes the QR factorization of A = Q*R,
024: *  and then computes the SVD of the 2-by-2 upper triangular matrix R.
025: *  The smaller singular value of R is returned in SSMIN, which is used
026: *  as the measurement of the linear dependency of the vectors X and Y.
027: *
028: *  Arguments
029: *  =========
030: *
031: *  N       (input) INTEGER
032: *          The length of the vectors X and Y.
033: *
034: *  X       (input/output) COMPLEX array, dimension (1+(N-1)*INCX)
035: *          On entry, X contains the N-vector X.
036: *          On exit, X is overwritten.
037: *
038: *  INCX    (input) INTEGER
039: *          The increment between successive elements of X. INCX > 0.
040: *
041: *  Y       (input/output) COMPLEX array, dimension (1+(N-1)*INCY)
042: *          On entry, Y contains the N-vector Y.
043: *          On exit, Y is overwritten.
044: *
045: *  INCY    (input) INTEGER
046: *          The increment between successive elements of Y. INCY > 0.
047: *
048: *  SSMIN   (output) REAL
049: *          The smallest singular value of the N-by-2 matrix A = ( X Y ).
050: *
051: *  =====================================================================
052: *
053: *     .. Parameters ..
054:       REAL               ZERO
055:       PARAMETER          ( ZERO = 0.0E+0 )
056:       COMPLEX            CONE
057:       PARAMETER          ( CONE = ( 1.0E+0, 0.0E+0 ) )
058: *     ..
059: *     .. Local Scalars ..
060:       REAL               SSMAX
061:       COMPLEX            A11, A12, A22, C, TAU
062: *     ..
063: *     .. Intrinsic Functions ..
064:       INTRINSIC          ABS, CONJG
065: *     ..
066: *     .. External Functions ..
067:       COMPLEX            CDOTC
068:       EXTERNAL           CDOTC
069: *     ..
070: *     .. External Subroutines ..
071:       EXTERNAL           CAXPY, CLARFG, SLAS2
072: *     ..
073: *     .. Executable Statements ..
074: *
075: *     Quick return if possible
076: *
077:       IF( N.LE.1 ) THEN
078:          SSMIN = ZERO
079:          RETURN
080:       END IF
081: *
082: *     Compute the QR factorization of the N-by-2 matrix ( X Y )
083: *
084:       CALL CLARFG( N, X( 1 ), X( 1+INCX ), INCX, TAU )
085:       A11 = X( 1 )
086:       X( 1 ) = CONE
087: *
088:       C = -CONJG( TAU )*CDOTC( N, X, INCX, Y, INCY )
089:       CALL CAXPY( N, C, X, INCX, Y, INCY )
090: *
091:       CALL CLARFG( N-1, Y( 1+INCY ), Y( 1+2*INCY ), INCY, TAU )
092: *
093:       A12 = Y( 1 )
094:       A22 = Y( 1+INCY )
095: *
096: *     Compute the SVD of 2-by-2 Upper triangular matrix.
097: *
098:       CALL SLAS2( ABS( A11 ), ABS( A12 ), ABS( A22 ), SSMIN, SSMAX )
099: *
100:       RETURN
101: *
102: *     End of CLAPLL
103: *
104:       END
105: