ENH: Improving the travis dashboard name
[platform/upstream/lapack.git] / SRC / zlapll.f
1 *> \brief \b ZLAPLL 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 ZLAPLL + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlapll.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlapll.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlapll.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE ZLAPLL( N, X, INCX, Y, INCY, SSMIN )
22 *
23 *       .. Scalar Arguments ..
24 *       INTEGER            INCX, INCY, N
25 *       DOUBLE PRECISION   SSMIN
26 *       ..
27 *       .. Array Arguments ..
28 *       COMPLEX*16         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 COMPLEX*16 array, dimension (1+(N-1)*INCX)
59 *>          On entry, X contains the N-vector X.
60 *>          On exit, X is overwritten.
61 *> \endverbatim
62 *>
63 *> \param[in] INCX
64 *> \verbatim
65 *>          INCX is INTEGER
66 *>          The increment between successive elements of X. INCX > 0.
67 *> \endverbatim
68 *>
69 *> \param[in,out] Y
70 *> \verbatim
71 *>          Y is COMPLEX*16 array, dimension (1+(N-1)*INCY)
72 *>          On entry, Y contains the N-vector Y.
73 *>          On exit, Y is overwritten.
74 *> \endverbatim
75 *>
76 *> \param[in] INCY
77 *> \verbatim
78 *>          INCY is INTEGER
79 *>          The increment between successive elements of Y. INCY > 0.
80 *> \endverbatim
81 *>
82 *> \param[out] SSMIN
83 *> \verbatim
84 *>          SSMIN is DOUBLE PRECISION
85 *>          The smallest singular value of the N-by-2 matrix A = ( X Y ).
86 *> \endverbatim
87 *
88 *  Authors:
89 *  ========
90 *
91 *> \author Univ. of Tennessee
92 *> \author Univ. of California Berkeley
93 *> \author Univ. of Colorado Denver
94 *> \author NAG Ltd.
95 *
96 *> \date September 2012
97 *
98 *> \ingroup complex16OTHERauxiliary
99 *
100 *  =====================================================================
101       SUBROUTINE ZLAPLL( N, X, INCX, Y, INCY, SSMIN )
102 *
103 *  -- LAPACK auxiliary routine (version 3.4.2) --
104 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
105 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
106 *     September 2012
107 *
108 *     .. Scalar Arguments ..
109       INTEGER            INCX, INCY, N
110       DOUBLE PRECISION   SSMIN
111 *     ..
112 *     .. Array Arguments ..
113       COMPLEX*16         X( * ), Y( * )
114 *     ..
115 *
116 *  =====================================================================
117 *
118 *     .. Parameters ..
119       DOUBLE PRECISION   ZERO
120       PARAMETER          ( ZERO = 0.0D+0 )
121       COMPLEX*16         CONE
122       PARAMETER          ( CONE = ( 1.0D+0, 0.0D+0 ) )
123 *     ..
124 *     .. Local Scalars ..
125       DOUBLE PRECISION   SSMAX
126       COMPLEX*16         A11, A12, A22, C, TAU
127 *     ..
128 *     .. Intrinsic Functions ..
129       INTRINSIC          ABS, DCONJG
130 *     ..
131 *     .. External Functions ..
132       COMPLEX*16         ZDOTC
133       EXTERNAL           ZDOTC
134 *     ..
135 *     .. External Subroutines ..
136       EXTERNAL           DLAS2, ZAXPY, ZLARFG
137 *     ..
138 *     .. Executable Statements ..
139 *
140 *     Quick return if possible
141 *
142       IF( N.LE.1 ) THEN
143          SSMIN = ZERO
144          RETURN
145       END IF
146 *
147 *     Compute the QR factorization of the N-by-2 matrix ( X Y )
148 *
149       CALL ZLARFG( N, X( 1 ), X( 1+INCX ), INCX, TAU )
150       A11 = X( 1 )
151       X( 1 ) = CONE
152 *
153       C = -DCONJG( TAU )*ZDOTC( N, X, INCX, Y, INCY )
154       CALL ZAXPY( N, C, X, INCX, Y, INCY )
155 *
156       CALL ZLARFG( N-1, Y( 1+INCY ), Y( 1+2*INCY ), INCY, TAU )
157 *
158       A12 = Y( 1 )
159       A22 = Y( 1+INCY )
160 *
161 *     Compute the SVD of 2-by-2 Upper triangular matrix.
162 *
163       CALL DLAS2( ABS( A11 ), ABS( A12 ), ABS( A22 ), SSMIN, SSMAX )
164 *
165       RETURN
166 *
167 *     End of ZLAPLL
168 *
169       END