LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ slaed9()

subroutine slaed9 ( integer  k,
integer  kstart,
integer  kstop,
integer  n,
real, dimension( * )  d,
real, dimension( ldq, * )  q,
integer  ldq,
real  rho,
real, dimension( * )  dlambda,
real, dimension( * )  w,
real, dimension( lds, * )  s,
integer  lds,
integer  info 
)

SLAED9 used by SSTEDC. Finds the roots of the secular equation and updates the eigenvectors. Used when the original matrix is dense.

Download SLAED9 + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 SLAED9 finds the roots of the secular equation, as defined by the
 values in D, Z, and RHO, between KSTART and KSTOP.  It makes the
 appropriate calls to SLAED4 and then stores the new matrix of
 eigenvectors for use in calculating the next level of Z vectors.
Parameters
[in]K
          K is INTEGER
          The number of terms in the rational function to be solved by
          SLAED4.  K >= 0.
[in]KSTART
          KSTART is INTEGER
[in]KSTOP
          KSTOP is INTEGER
          The updated eigenvalues Lambda(I), KSTART <= I <= KSTOP
          are to be computed.  1 <= KSTART <= KSTOP <= K.
[in]N
          N is INTEGER
          The number of rows and columns in the Q matrix.
          N >= K (delation may result in N > K).
[out]D
          D is REAL array, dimension (N)
          D(I) contains the updated eigenvalues
          for KSTART <= I <= KSTOP.
[out]Q
          Q is REAL array, dimension (LDQ,N)
[in]LDQ
          LDQ is INTEGER
          The leading dimension of the array Q.  LDQ >= max( 1, N ).
[in]RHO
          RHO is REAL
          The value of the parameter in the rank one update equation.
          RHO >= 0 required.
[in]DLAMBDA
          DLAMBDA is REAL array, dimension (K)
          The first K elements of this array contain the old roots
          of the deflated updating problem.  These are the poles
          of the secular equation.
[in]W
          W is REAL array, dimension (K)
          The first K elements of this array contain the components
          of the deflation-adjusted updating vector.
[out]S
          S is REAL array, dimension (LDS, K)
          Will contain the eigenvectors of the repaired matrix which
          will be stored for subsequent Z vector calculation and
          multiplied by the previously accumulated eigenvectors
          to update the system.
[in]LDS
          LDS is INTEGER
          The leading dimension of S.  LDS >= max( 1, K ).
[out]INFO
          INFO is INTEGER
          = 0:  successful exit.
          < 0:  if INFO = -i, the i-th argument had an illegal value.
          > 0:  if INFO = 1, an eigenvalue did not converge
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Contributors:
Jeff Rutter, Computer Science Division, University of California at Berkeley, USA

Definition at line 154 of file slaed9.f.

156*
157* -- LAPACK computational routine --
158* -- LAPACK is a software package provided by Univ. of Tennessee, --
159* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
160*
161* .. Scalar Arguments ..
162 INTEGER INFO, K, KSTART, KSTOP, LDQ, LDS, N
163 REAL RHO
164* ..
165* .. Array Arguments ..
166 REAL D( * ), DLAMBDA( * ), Q( LDQ, * ), S( LDS, * ),
167 $ W( * )
168* ..
169*
170* =====================================================================
171*
172* .. Local Scalars ..
173 INTEGER I, J
174 REAL TEMP
175* ..
176* .. External Functions ..
177 REAL SNRM2
178 EXTERNAL snrm2
179* ..
180* .. External Subroutines ..
181 EXTERNAL scopy, slaed4, xerbla
182* ..
183* .. Intrinsic Functions ..
184 INTRINSIC max, sign, sqrt
185* ..
186* .. Executable Statements ..
187*
188* Test the input parameters.
189*
190 info = 0
191*
192 IF( k.LT.0 ) THEN
193 info = -1
194 ELSE IF( kstart.LT.1 .OR. kstart.GT.max( 1, k ) ) THEN
195 info = -2
196 ELSE IF( max( 1, kstop ).LT.kstart .OR. kstop.GT.max( 1, k ) )
197 $ THEN
198 info = -3
199 ELSE IF( n.LT.k ) THEN
200 info = -4
201 ELSE IF( ldq.LT.max( 1, k ) ) THEN
202 info = -7
203 ELSE IF( lds.LT.max( 1, k ) ) THEN
204 info = -12
205 END IF
206 IF( info.NE.0 ) THEN
207 CALL xerbla( 'SLAED9', -info )
208 RETURN
209 END IF
210*
211* Quick return if possible
212*
213 IF( k.EQ.0 )
214 $ RETURN
215*
216 DO 20 j = kstart, kstop
217 CALL slaed4( k, j, dlambda, w, q( 1, j ), rho, d( j ), info )
218*
219* If the zero finder fails, the computation is terminated.
220*
221 IF( info.NE.0 )
222 $ GO TO 120
223 20 CONTINUE
224*
225 IF( k.EQ.1 .OR. k.EQ.2 ) THEN
226 DO 40 i = 1, k
227 DO 30 j = 1, k
228 s( j, i ) = q( j, i )
229 30 CONTINUE
230 40 CONTINUE
231 GO TO 120
232 END IF
233*
234* Compute updated W.
235*
236 CALL scopy( k, w, 1, s, 1 )
237*
238* Initialize W(I) = Q(I,I)
239*
240 CALL scopy( k, q, ldq+1, w, 1 )
241 DO 70 j = 1, k
242 DO 50 i = 1, j - 1
243 w( i ) = w( i )*( q( i, j )/( dlambda( i )-dlambda( j ) ) )
244 50 CONTINUE
245 DO 60 i = j + 1, k
246 w( i ) = w( i )*( q( i, j )/( dlambda( i )-dlambda( j ) ) )
247 60 CONTINUE
248 70 CONTINUE
249 DO 80 i = 1, k
250 w( i ) = sign( sqrt( -w( i ) ), s( i, 1 ) )
251 80 CONTINUE
252*
253* Compute eigenvectors of the modified rank-1 modification.
254*
255 DO 110 j = 1, k
256 DO 90 i = 1, k
257 q( i, j ) = w( i ) / q( i, j )
258 90 CONTINUE
259 temp = snrm2( k, q( 1, j ), 1 )
260 DO 100 i = 1, k
261 s( i, j ) = q( i, j ) / temp
262 100 CONTINUE
263 110 CONTINUE
264*
265 120 CONTINUE
266 RETURN
267*
268* End of SLAED9
269*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine scopy(n, sx, incx, sy, incy)
SCOPY
Definition scopy.f:82
subroutine slaed4(n, i, d, z, delta, rho, dlam, info)
SLAED4 used by SSTEDC. Finds a single root of the secular equation.
Definition slaed4.f:145
real(wp) function snrm2(n, x, incx)
SNRM2
Definition snrm2.f90:89
Here is the call graph for this function:
Here is the caller graph for this function: