1 *> \brief \b DLAED3 used by sstedc. Finds the roots of the secular equation and updates the eigenvectors. Used when the original matrix is tridiagonal.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DLAED3 + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dlaed3.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dlaed3.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dlaed3.f">
21 * SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX,
24 * .. Scalar Arguments ..
25 * INTEGER INFO, K, LDQ, N, N1
26 * DOUBLE PRECISION RHO
28 * .. Array Arguments ..
29 * INTEGER CTOT( * ), INDX( * )
30 * DOUBLE PRECISION D( * ), DLAMDA( * ), Q( LDQ, * ), Q2( * ),
40 *> DLAED3 finds the roots of the secular equation, as defined by the
41 *> values in D, W, and RHO, between 1 and K. It makes the
42 *> appropriate calls to DLAED4 and then updates the eigenvectors by
43 *> multiplying the matrix of eigenvectors of the pair of eigensystems
44 *> being combined by the matrix of eigenvectors of the K-by-K system
45 *> which is solved here.
47 *> This code makes very mild assumptions about floating point
48 *> arithmetic. It will work on machines with a guard digit in
49 *> add/subtract, or on those binary machines without guard digits
50 *> which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or Cray-2.
51 *> It could conceivably fail on hexadecimal or decimal machines
52 *> without guard digits, but we know of none.
61 *> The number of terms in the rational function to be solved by
68 *> The number of rows and columns in the Q matrix.
69 *> N >= K (deflation may result in N>K).
75 *> The location of the last eigenvalue in the leading submatrix.
76 *> min(1,N) <= N1 <= N/2.
81 *> D is DOUBLE PRECISION array, dimension (N)
82 *> D(I) contains the updated eigenvalues for
88 *> Q is DOUBLE PRECISION array, dimension (LDQ,N)
89 *> Initially the first K columns are used as workspace.
90 *> On output the columns 1 to K contain
91 *> the updated eigenvectors.
97 *> The leading dimension of the array Q. LDQ >= max(1,N).
102 *> RHO is DOUBLE PRECISION
103 *> The value of the parameter in the rank one update equation.
104 *> RHO >= 0 required.
107 *> \param[in,out] DLAMDA
109 *> DLAMDA is DOUBLE PRECISION array, dimension (K)
110 *> The first K elements of this array contain the old roots
111 *> of the deflated updating problem. These are the poles
112 *> of the secular equation. May be changed on output by
113 *> having lowest order bit set to zero on Cray X-MP, Cray Y-MP,
114 *> Cray-2, or Cray C-90, as described above.
119 *> Q2 is DOUBLE PRECISION array, dimension (LDQ2, N)
120 *> The first K columns of this matrix contain the non-deflated
121 *> eigenvectors for the split problem.
126 *> INDX is INTEGER array, dimension (N)
127 *> The permutation used to arrange the columns of the deflated
128 *> Q matrix into three groups (see DLAED2).
129 *> The rows of the eigenvectors found by DLAED4 must be likewise
130 *> permuted before the matrix multiply can take place.
135 *> CTOT is INTEGER array, dimension (4)
136 *> A count of the total number of the various types of columns
137 *> in Q, as described in INDX. The fourth column type is any
138 *> column which has been deflated.
143 *> W is DOUBLE PRECISION array, dimension (K)
144 *> The first K elements of this array contain the components
145 *> of the deflation-adjusted updating vector. Destroyed on
151 *> S is DOUBLE PRECISION array, dimension (N1 + 1)*K
152 *> Will contain the eigenvectors of the repaired matrix which
153 *> will be multiplied by the previously accumulated eigenvectors
154 *> to update the system.
160 *> = 0: successful exit.
161 *> < 0: if INFO = -i, the i-th argument had an illegal value.
162 *> > 0: if INFO = 1, an eigenvalue did not converge
168 *> \author Univ. of Tennessee
169 *> \author Univ. of California Berkeley
170 *> \author Univ. of Colorado Denver
173 *> \date September 2012
175 *> \ingroup auxOTHERcomputational
177 *> \par Contributors:
180 *> Jeff Rutter, Computer Science Division, University of California
181 *> at Berkeley, USA \n
182 *> Modified by Francoise Tisseur, University of Tennessee
184 * =====================================================================
185 SUBROUTINE DLAED3( K, N, N1, D, Q, LDQ, RHO, DLAMDA, Q2, INDX,
188 * -- LAPACK computational routine (version 3.4.2) --
189 * -- LAPACK is a software package provided by Univ. of Tennessee, --
190 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
193 * .. Scalar Arguments ..
194 INTEGER INFO, K, LDQ, N, N1
197 * .. Array Arguments ..
198 INTEGER CTOT( * ), INDX( * )
199 DOUBLE PRECISION D( * ), DLAMDA( * ), Q( LDQ, * ), Q2( * ),
203 * =====================================================================
206 DOUBLE PRECISION ONE, ZERO
207 PARAMETER ( ONE = 1.0D0, ZERO = 0.0D0 )
209 * .. Local Scalars ..
210 INTEGER I, II, IQ2, J, N12, N2, N23
211 DOUBLE PRECISION TEMP
213 * .. External Functions ..
214 DOUBLE PRECISION DLAMC3, DNRM2
215 EXTERNAL DLAMC3, DNRM2
217 * .. External Subroutines ..
218 EXTERNAL DCOPY, DGEMM, DLACPY, DLAED4, DLASET, XERBLA
220 * .. Intrinsic Functions ..
221 INTRINSIC MAX, SIGN, SQRT
223 * .. Executable Statements ..
225 * Test the input parameters.
231 ELSE IF( N.LT.K ) THEN
233 ELSE IF( LDQ.LT.MAX( 1, N ) ) THEN
237 CALL XERBLA( 'DLAED3', -INFO )
241 * Quick return if possible
246 * Modify values DLAMDA(i) to make sure all DLAMDA(i)-DLAMDA(j) can
247 * be computed with high relative accuracy (barring over/underflow).
248 * This is a problem on machines without a guard digit in
249 * add/subtract (Cray XMP, Cray YMP, Cray C 90 and Cray 2).
250 * The following code replaces DLAMDA(I) by 2*DLAMDA(I)-DLAMDA(I),
251 * which on any of these machines zeros out the bottommost
252 * bit of DLAMDA(I) if it is 1; this makes the subsequent
253 * subtractions DLAMDA(I)-DLAMDA(J) unproblematic when cancellation
254 * occurs. On binary machines with a guard digit (almost all
255 * machines) it does not change DLAMDA(I) at all. On hexadecimal
256 * and decimal machines with a guard digit, it slightly
257 * changes the bottommost bits of DLAMDA(I). It does not account
258 * for hexadecimal or decimal machines without guard digits
259 * (we know of none). We use a subroutine call to compute
260 * 2*DLAMBDA(I) to prevent optimizing compilers from eliminating
264 DLAMDA( I ) = DLAMC3( DLAMDA( I ), DLAMDA( I ) ) - DLAMDA( I )
268 CALL DLAED4( K, J, DLAMDA, W, Q( 1, J ), RHO, D( J ), INFO )
270 * If the zero finder fails, the computation is terminated.
292 CALL DCOPY( K, W, 1, S, 1 )
294 * Initialize W(I) = Q(I,I)
296 CALL DCOPY( K, Q, LDQ+1, W, 1 )
299 W( I ) = W( I )*( Q( I, J ) / ( DLAMDA( I )-DLAMDA( J ) ) )
302 W( I ) = W( I )*( Q( I, J ) / ( DLAMDA( I )-DLAMDA( J ) ) )
306 W( I ) = SIGN( SQRT( -W( I ) ), S( I ) )
309 * Compute eigenvectors of the modified rank-1 modification.
313 S( I ) = W( I ) / Q( I, J )
315 TEMP = DNRM2( K, S, 1 )
318 Q( I, J ) = S( II ) / TEMP
322 * Compute the updated eigenvectors.
327 N12 = CTOT( 1 ) + CTOT( 2 )
328 N23 = CTOT( 2 ) + CTOT( 3 )
330 CALL DLACPY( 'A', N23, K, Q( CTOT( 1 )+1, 1 ), LDQ, S, N23 )
333 CALL DGEMM( 'N', 'N', N2, K, N23, ONE, Q2( IQ2 ), N2, S, N23,
334 $ ZERO, Q( N1+1, 1 ), LDQ )
336 CALL DLASET( 'A', N2, K, ZERO, ZERO, Q( N1+1, 1 ), LDQ )
339 CALL DLACPY( 'A', N12, K, Q, LDQ, S, N12 )
341 CALL DGEMM( 'N', 'N', N1, K, N12, ONE, Q2, N1, S, N12, ZERO, Q,
344 CALL DLASET( 'A', N1, K, ZERO, ZERO, Q( 1, 1 ), LDQ )