001:       SUBROUTINE SLAPLL( 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:       REAL               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) REAL array,
035: *                         dimension (1+(N-1)*INCX)
036: *          On entry, X contains the N-vector X.
037: *          On exit, X is overwritten.
038: *
039: *  INCX    (input) INTEGER
040: *          The increment between successive elements of X. INCX > 0.
041: *
042: *  Y       (input/output) REAL array,
043: *                         dimension (1+(N-1)*INCY)
044: *          On entry, Y contains the N-vector Y.
045: *          On exit, Y is overwritten.
046: *
047: *  INCY    (input) INTEGER
048: *          The increment between successive elements of Y. INCY > 0.
049: *
050: *  SSMIN   (output) REAL
051: *          The smallest singular value of the N-by-2 matrix A = ( X Y ).
052: *
053: *  =====================================================================
054: *
055: *     .. Parameters ..
056:       REAL               ZERO, ONE
057:       PARAMETER          ( ZERO = 0.0E+0, ONE = 1.0E+0 )
058: *     ..
059: *     .. Local Scalars ..
060:       REAL               A11, A12, A22, C, SSMAX, TAU
061: *     ..
062: *     .. External Functions ..
063:       REAL               SDOT
064:       EXTERNAL           SDOT
065: *     ..
066: *     .. External Subroutines ..
067:       EXTERNAL           SAXPY, SLARFG, SLAS2
068: *     ..
069: *     .. Executable Statements ..
070: *
071: *     Quick return if possible
072: *
073:       IF( N.LE.1 ) THEN
074:          SSMIN = ZERO
075:          RETURN
076:       END IF
077: *
078: *     Compute the QR factorization of the N-by-2 matrix ( X Y )
079: *
080:       CALL SLARFG( N, X( 1 ), X( 1+INCX ), INCX, TAU )
081:       A11 = X( 1 )
082:       X( 1 ) = ONE
083: *
084:       C = -TAU*SDOT( N, X, INCX, Y, INCY )
085:       CALL SAXPY( N, C, X, INCX, Y, INCY )
086: *
087:       CALL SLARFG( N-1, Y( 1+INCY ), Y( 1+2*INCY ), INCY, TAU )
088: *
089:       A12 = Y( 1 )
090:       A22 = Y( 1+INCY )
091: *
092: *     Compute the SVD of 2-by-2 Upper triangular matrix.
093: *
094:       CALL SLAS2( A11, A12, A22, SSMIN, SSMAX )
095: *
096:       RETURN
097: *
098: *     End of SLAPLL
099: *
100:       END
101: