1 *> \brief \b SLASQ1 computes the singular values of a real square bidiagonal matrix. Used by sbdsqr.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SLASQ1 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/slasq1.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/slasq1.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/slasq1.f">
21 * SUBROUTINE SLASQ1( N, D, E, WORK, INFO )
23 * .. Scalar Arguments ..
26 * .. Array Arguments ..
27 * REAL D( * ), E( * ), WORK( * )
36 *> SLASQ1 computes the singular values of a real N-by-N bidiagonal
37 *> matrix with diagonal D and off-diagonal E. The singular values
38 *> are computed to high relative accuracy, in the absence of
39 *> denormalization, underflow and overflow. The algorithm was first
42 *> "Accurate singular values and differential qd algorithms" by K. V.
43 *> Fernando and B. N. Parlett, Numer. Math., Vol-67, No. 2, pp. 191-230,
46 *> and the present implementation is described in "An implementation of
47 *> the dqds Algorithm (Positive Case)", LAPACK Working Note.
56 *> The number of rows and columns in the matrix. N >= 0.
61 *> D is REAL array, dimension (N)
62 *> On entry, D contains the diagonal elements of the
63 *> bidiagonal matrix whose SVD is desired. On normal exit,
64 *> D contains the singular values in decreasing order.
69 *> E is REAL array, dimension (N)
70 *> On entry, elements E(1:N-1) contain the off-diagonal elements
71 *> of the bidiagonal matrix whose SVD is desired.
72 *> On exit, E is overwritten.
77 *> WORK is REAL array, dimension (4*N)
83 *> = 0: successful exit
84 *> < 0: if INFO = -i, the i-th argument had an illegal value
85 *> > 0: the algorithm failed
86 *> = 1, a split was marked by a positive value in E
87 *> = 2, current block of Z not diagonalized after 100*N
88 *> iterations (in inner while loop) On exit D and E
89 *> represent a matrix with the same singular values
90 *> which the calling subroutine could use to finish the
91 *> computation, or even feed back into SLASQ1
92 *> = 3, termination criterion of outer while loop not met
93 *> (program created more than N unreduced blocks)
99 *> \author Univ. of Tennessee
100 *> \author Univ. of California Berkeley
101 *> \author Univ. of Colorado Denver
104 *> \date November 2015
106 *> \ingroup auxOTHERcomputational
108 * =====================================================================
109 SUBROUTINE SLASQ1( N, D, E, WORK, INFO )
111 * -- LAPACK computational routine (version 3.6.0) --
112 * -- LAPACK is a software package provided by Univ. of Tennessee, --
113 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
116 * .. Scalar Arguments ..
119 * .. Array Arguments ..
120 REAL D( * ), E( * ), WORK( * )
123 * =====================================================================
127 PARAMETER ( ZERO = 0.0E0 )
129 * .. Local Scalars ..
131 REAL EPS, SCALE, SAFMIN, SIGMN, SIGMX
133 * .. External Subroutines ..
134 EXTERNAL SCOPY, SLAS2, SLASCL, SLASQ2, SLASRT, XERBLA
136 * .. External Functions ..
140 * .. Intrinsic Functions ..
141 INTRINSIC ABS, MAX, SQRT
143 * .. Executable Statements ..
148 CALL XERBLA( 'SLASQ1', -INFO )
150 ELSE IF( N.EQ.0 ) THEN
152 ELSE IF( N.EQ.1 ) THEN
153 D( 1 ) = ABS( D( 1 ) )
155 ELSE IF( N.EQ.2 ) THEN
156 CALL SLAS2( D( 1 ), E( 1 ), D( 2 ), SIGMN, SIGMX )
162 * Estimate the largest singular value.
166 D( I ) = ABS( D( I ) )
167 SIGMX = MAX( SIGMX, ABS( E( I ) ) )
169 D( N ) = ABS( D( N ) )
171 * Early return if SIGMX is zero (matrix is already diagonal).
173 IF( SIGMX.EQ.ZERO ) THEN
174 CALL SLASRT( 'D', N, D, IINFO )
179 SIGMX = MAX( SIGMX, D( I ) )
182 * Copy D and E into WORK (in the Z format) and scale (squaring the
183 * input data makes scaling by a power of the radix pointless).
185 EPS = SLAMCH( 'Precision' )
186 SAFMIN = SLAMCH( 'Safe minimum' )
187 SCALE = SQRT( EPS / SAFMIN )
188 CALL SCOPY( N, D, 1, WORK( 1 ), 2 )
189 CALL SCOPY( N-1, E, 1, WORK( 2 ), 2 )
190 CALL SLASCL( 'G', 0, 0, SIGMX, SCALE, 2*N-1, 1, WORK, 2*N-1,
193 * Compute the q's and e's.
196 WORK( I ) = WORK( I )**2
200 CALL SLASQ2( N, WORK, INFO )
204 D( I ) = SQRT( WORK( I ) )
206 CALL SLASCL( 'G', 0, 0, SCALE, SIGMX, N, 1, D, N, IINFO )
207 ELSE IF( INFO.EQ.2 ) THEN
209 * Maximum number of iterations exceeded. Move data from WORK
210 * into D and E so the calling subroutine can try to finish
213 D( I ) = SQRT( WORK( 2*I-1 ) )
214 E( I ) = SQRT( WORK( 2*I ) )
216 CALL SLASCL( 'G', 0, 0, SCALE, SIGMX, N, 1, D, N, IINFO )
217 CALL SLASCL( 'G', 0, 0, SCALE, SIGMX, N, 1, E, N, IINFO )