LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dlapll.f
Go to the documentation of this file.
1*> \brief \b DLAPLL measures the linear dependence of two vectors.
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download DLAPLL + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlapll.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlapll.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlapll.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE DLAPLL( N, X, INCX, Y, INCY, SSMIN )
22*
23* .. Scalar Arguments ..
24* INTEGER INCX, INCY, N
25* DOUBLE PRECISION SSMIN
26* ..
27* .. Array Arguments ..
28* DOUBLE PRECISION X( * ), Y( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> Given two column vectors X and Y, let
38*>
39*> A = ( X Y ).
40*>
41*> The subroutine first computes the QR factorization of A = Q*R,
42*> and then computes the SVD of the 2-by-2 upper triangular matrix R.
43*> The smaller singular value of R is returned in SSMIN, which is used
44*> as the measurement of the linear dependency of the vectors X and Y.
45*> \endverbatim
46*
47* Arguments:
48* ==========
49*
50*> \param[in] N
51*> \verbatim
52*> N is INTEGER
53*> The length of the vectors X and Y.
54*> \endverbatim
55*>
56*> \param[in,out] X
57*> \verbatim
58*> X is DOUBLE PRECISION array,
59*> dimension (1+(N-1)*INCX)
60*> On entry, X contains the N-vector X.
61*> On exit, X is overwritten.
62*> \endverbatim
63*>
64*> \param[in] INCX
65*> \verbatim
66*> INCX is INTEGER
67*> The increment between successive elements of X. INCX > 0.
68*> \endverbatim
69*>
70*> \param[in,out] Y
71*> \verbatim
72*> Y is DOUBLE PRECISION array,
73*> dimension (1+(N-1)*INCY)
74*> On entry, Y contains the N-vector Y.
75*> On exit, Y is overwritten.
76*> \endverbatim
77*>
78*> \param[in] INCY
79*> \verbatim
80*> INCY is INTEGER
81*> The increment between successive elements of Y. INCY > 0.
82*> \endverbatim
83*>
84*> \param[out] SSMIN
85*> \verbatim
86*> SSMIN is DOUBLE PRECISION
87*> The smallest singular value of the N-by-2 matrix A = ( X Y ).
88*> \endverbatim
89*
90* Authors:
91* ========
92*
93*> \author Univ. of Tennessee
94*> \author Univ. of California Berkeley
95*> \author Univ. of Colorado Denver
96*> \author NAG Ltd.
97*
98*> \ingroup lapll
99*
100* =====================================================================
101 SUBROUTINE dlapll( N, X, INCX, Y, INCY, SSMIN )
102*
103* -- LAPACK auxiliary routine --
104* -- LAPACK is a software package provided by Univ. of Tennessee, --
105* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106*
107* .. Scalar Arguments ..
108 INTEGER INCX, INCY, N
109 DOUBLE PRECISION SSMIN
110* ..
111* .. Array Arguments ..
112 DOUBLE PRECISION X( * ), Y( * )
113* ..
114*
115* =====================================================================
116*
117* .. Parameters ..
118 DOUBLE PRECISION ZERO, ONE
119 parameter( zero = 0.0d+0, one = 1.0d+0 )
120* ..
121* .. Local Scalars ..
122 DOUBLE PRECISION A11, A12, A22, C, SSMAX, TAU
123* ..
124* .. External Functions ..
125 DOUBLE PRECISION DDOT
126 EXTERNAL ddot
127* ..
128* .. External Subroutines ..
129 EXTERNAL daxpy, dlarfg, dlas2
130* ..
131* .. Executable Statements ..
132*
133* Quick return if possible
134*
135 IF( n.LE.1 ) THEN
136 ssmin = zero
137 RETURN
138 END IF
139*
140* Compute the QR factorization of the N-by-2 matrix ( X Y )
141*
142 CALL dlarfg( n, x( 1 ), x( 1+incx ), incx, tau )
143 a11 = x( 1 )
144 x( 1 ) = one
145*
146 c = -tau*ddot( n, x, incx, y, incy )
147 CALL daxpy( n, c, x, incx, y, incy )
148*
149 CALL dlarfg( n-1, y( 1+incy ), y( 1+2*incy ), incy, tau )
150*
151 a12 = y( 1 )
152 a22 = y( 1+incy )
153*
154* Compute the SVD of 2-by-2 Upper triangular matrix.
155*
156 CALL dlas2( a11, a12, a22, ssmin, ssmax )
157*
158 RETURN
159*
160* End of DLAPLL
161*
162 END
subroutine daxpy(n, da, dx, incx, dy, incy)
DAXPY
Definition daxpy.f:89
subroutine dlapll(n, x, incx, y, incy, ssmin)
DLAPLL measures the linear dependence of two vectors.
Definition dlapll.f:102
subroutine dlarfg(n, alpha, x, incx, tau)
DLARFG generates an elementary reflector (Householder matrix).
Definition dlarfg.f:106
subroutine dlas2(f, g, h, ssmin, ssmax)
DLAS2 computes singular values of a 2-by-2 triangular matrix.
Definition dlas2.f:105