LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dstevr.f
Go to the documentation of this file.
1 *> \brief <b> DSTEVR computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matrices</b>
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download DSTEVR + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dstevr.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dstevr.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dstevr.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE DSTEVR( JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL,
22 * M, W, Z, LDZ, ISUPPZ, WORK, LWORK, IWORK,
23 * LIWORK, INFO )
24 *
25 * .. Scalar Arguments ..
26 * CHARACTER JOBZ, RANGE
27 * INTEGER IL, INFO, IU, LDZ, LIWORK, LWORK, M, N
28 * DOUBLE PRECISION ABSTOL, VL, VU
29 * ..
30 * .. Array Arguments ..
31 * INTEGER ISUPPZ( * ), IWORK( * )
32 * DOUBLE PRECISION D( * ), E( * ), W( * ), WORK( * ), Z( LDZ, * )
33 * ..
34 *
35 *
36 *> \par Purpose:
37 * =============
38 *>
39 *> \verbatim
40 *>
41 *> DSTEVR computes selected eigenvalues and, optionally, eigenvectors
42 *> of a real symmetric tridiagonal matrix T. Eigenvalues and
43 *> eigenvectors can be selected by specifying either a range of values
44 *> or a range of indices for the desired eigenvalues.
45 *>
46 *> Whenever possible, DSTEVR calls DSTEMR to compute the
47 *> eigenspectrum using Relatively Robust Representations. DSTEMR
48 *> computes eigenvalues by the dqds algorithm, while orthogonal
49 *> eigenvectors are computed from various "good" L D L^T representations
50 *> (also known as Relatively Robust Representations). Gram-Schmidt
51 *> orthogonalization is avoided as far as possible. More specifically,
52 *> the various steps of the algorithm are as follows. For the i-th
53 *> unreduced block of T,
54 *> (a) Compute T - sigma_i = L_i D_i L_i^T, such that L_i D_i L_i^T
55 *> is a relatively robust representation,
56 *> (b) Compute the eigenvalues, lambda_j, of L_i D_i L_i^T to high
57 *> relative accuracy by the dqds algorithm,
58 *> (c) If there is a cluster of close eigenvalues, "choose" sigma_i
59 *> close to the cluster, and go to step (a),
60 *> (d) Given the approximate eigenvalue lambda_j of L_i D_i L_i^T,
61 *> compute the corresponding eigenvector by forming a
62 *> rank-revealing twisted factorization.
63 *> The desired accuracy of the output can be specified by the input
64 *> parameter ABSTOL.
65 *>
66 *> For more details, see "A new O(n^2) algorithm for the symmetric
67 *> tridiagonal eigenvalue/eigenvector problem", by Inderjit Dhillon,
68 *> Computer Science Division Technical Report No. UCB//CSD-97-971,
69 *> UC Berkeley, May 1997.
70 *>
71 *>
72 *> Note 1 : DSTEVR calls DSTEMR when the full spectrum is requested
73 *> on machines which conform to the ieee-754 floating point standard.
74 *> DSTEVR calls DSTEBZ and DSTEIN on non-ieee machines and
75 *> when partial spectrum requests are made.
76 *>
77 *> Normal execution of DSTEMR may create NaNs and infinities and
78 *> hence may abort due to a floating point exception in environments
79 *> which do not handle NaNs and infinities in the ieee standard default
80 *> manner.
81 *> \endverbatim
82 *
83 * Arguments:
84 * ==========
85 *
86 *> \param[in] JOBZ
87 *> \verbatim
88 *> JOBZ is CHARACTER*1
89 *> = 'N': Compute eigenvalues only;
90 *> = 'V': Compute eigenvalues and eigenvectors.
91 *> \endverbatim
92 *>
93 *> \param[in] RANGE
94 *> \verbatim
95 *> RANGE is CHARACTER*1
96 *> = 'A': all eigenvalues will be found.
97 *> = 'V': all eigenvalues in the half-open interval (VL,VU]
98 *> will be found.
99 *> = 'I': the IL-th through IU-th eigenvalues will be found.
100 *> For RANGE = 'V' or 'I' and IU - IL < N - 1, DSTEBZ and
101 *> DSTEIN are called
102 *> \endverbatim
103 *>
104 *> \param[in] N
105 *> \verbatim
106 *> N is INTEGER
107 *> The order of the matrix. N >= 0.
108 *> \endverbatim
109 *>
110 *> \param[in,out] D
111 *> \verbatim
112 *> D is DOUBLE PRECISION array, dimension (N)
113 *> On entry, the n diagonal elements of the tridiagonal matrix
114 *> A.
115 *> On exit, D may be multiplied by a constant factor chosen
116 *> to avoid over/underflow in computing the eigenvalues.
117 *> \endverbatim
118 *>
119 *> \param[in,out] E
120 *> \verbatim
121 *> E is DOUBLE PRECISION array, dimension (max(1,N-1))
122 *> On entry, the (n-1) subdiagonal elements of the tridiagonal
123 *> matrix A in elements 1 to N-1 of E.
124 *> On exit, E may be multiplied by a constant factor chosen
125 *> to avoid over/underflow in computing the eigenvalues.
126 *> \endverbatim
127 *>
128 *> \param[in] VL
129 *> \verbatim
130 *> VL is DOUBLE PRECISION
131 *> If RANGE='V', the lower bound of the interval to
132 *> be searched for eigenvalues. VL < VU.
133 *> Not referenced if RANGE = 'A' or 'I'.
134 *> \endverbatim
135 *>
136 *> \param[in] VU
137 *> \verbatim
138 *> VU is DOUBLE PRECISION
139 *> If RANGE='V', the upper bound of the interval to
140 *> be searched for eigenvalues. VL < VU.
141 *> Not referenced if RANGE = 'A' or 'I'.
142 *> \endverbatim
143 *>
144 *> \param[in] IL
145 *> \verbatim
146 *> IL is INTEGER
147 *> If RANGE='I', the index of the
148 *> smallest eigenvalue to be returned.
149 *> 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
150 *> Not referenced if RANGE = 'A' or 'V'.
151 *> \endverbatim
152 *>
153 *> \param[in] IU
154 *> \verbatim
155 *> IU is INTEGER
156 *> If RANGE='I', the index of the
157 *> largest eigenvalue to be returned.
158 *> 1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.
159 *> Not referenced if RANGE = 'A' or 'V'.
160 *> \endverbatim
161 *>
162 *> \param[in] ABSTOL
163 *> \verbatim
164 *> ABSTOL is DOUBLE PRECISION
165 *> The absolute error tolerance for the eigenvalues.
166 *> An approximate eigenvalue is accepted as converged
167 *> when it is determined to lie in an interval [a,b]
168 *> of width less than or equal to
169 *>
170 *> ABSTOL + EPS * max( |a|,|b| ) ,
171 *>
172 *> where EPS is the machine precision. If ABSTOL is less than
173 *> or equal to zero, then EPS*|T| will be used in its place,
174 *> where |T| is the 1-norm of the tridiagonal matrix obtained
175 *> by reducing A to tridiagonal form.
176 *>
177 *> See "Computing Small Singular Values of Bidiagonal Matrices
178 *> with Guaranteed High Relative Accuracy," by Demmel and
179 *> Kahan, LAPACK Working Note #3.
180 *>
181 *> If high relative accuracy is important, set ABSTOL to
182 *> DLAMCH( 'Safe minimum' ). Doing so will guarantee that
183 *> eigenvalues are computed to high relative accuracy when
184 *> possible in future releases. The current code does not
185 *> make any guarantees about high relative accuracy, but
186 *> future releases will. See J. Barlow and J. Demmel,
187 *> "Computing Accurate Eigensystems of Scaled Diagonally
188 *> Dominant Matrices", LAPACK Working Note #7, for a discussion
189 *> of which matrices define their eigenvalues to high relative
190 *> accuracy.
191 *> \endverbatim
192 *>
193 *> \param[out] M
194 *> \verbatim
195 *> M is INTEGER
196 *> The total number of eigenvalues found. 0 <= M <= N.
197 *> If RANGE = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
198 *> \endverbatim
199 *>
200 *> \param[out] W
201 *> \verbatim
202 *> W is DOUBLE PRECISION array, dimension (N)
203 *> The first M elements contain the selected eigenvalues in
204 *> ascending order.
205 *> \endverbatim
206 *>
207 *> \param[out] Z
208 *> \verbatim
209 *> Z is DOUBLE PRECISION array, dimension (LDZ, max(1,M) )
210 *> If JOBZ = 'V', then if INFO = 0, the first M columns of Z
211 *> contain the orthonormal eigenvectors of the matrix A
212 *> corresponding to the selected eigenvalues, with the i-th
213 *> column of Z holding the eigenvector associated with W(i).
214 *> Note: the user must ensure that at least max(1,M) columns are
215 *> supplied in the array Z; if RANGE = 'V', the exact value of M
216 *> is not known in advance and an upper bound must be used.
217 *> \endverbatim
218 *>
219 *> \param[in] LDZ
220 *> \verbatim
221 *> LDZ is INTEGER
222 *> The leading dimension of the array Z. LDZ >= 1, and if
223 *> JOBZ = 'V', LDZ >= max(1,N).
224 *> \endverbatim
225 *>
226 *> \param[out] ISUPPZ
227 *> \verbatim
228 *> ISUPPZ is INTEGER array, dimension ( 2*max(1,M) )
229 *> The support of the eigenvectors in Z, i.e., the indices
230 *> indicating the nonzero elements in Z. The i-th eigenvector
231 *> is nonzero only in elements ISUPPZ( 2*i-1 ) through
232 *> ISUPPZ( 2*i ).
233 *> Implemented only for RANGE = 'A' or 'I' and IU - IL = N - 1
234 *> \endverbatim
235 *>
236 *> \param[out] WORK
237 *> \verbatim
238 *> WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK))
239 *> On exit, if INFO = 0, WORK(1) returns the optimal (and
240 *> minimal) LWORK.
241 *> \endverbatim
242 *>
243 *> \param[in] LWORK
244 *> \verbatim
245 *> LWORK is INTEGER
246 *> The dimension of the array WORK. LWORK >= max(1,20*N).
247 *>
248 *> If LWORK = -1, then a workspace query is assumed; the routine
249 *> only calculates the optimal sizes of the WORK and IWORK
250 *> arrays, returns these values as the first entries of the WORK
251 *> and IWORK arrays, and no error message related to LWORK or
252 *> LIWORK is issued by XERBLA.
253 *> \endverbatim
254 *>
255 *> \param[out] IWORK
256 *> \verbatim
257 *> IWORK is INTEGER array, dimension (MAX(1,LIWORK))
258 *> On exit, if INFO = 0, IWORK(1) returns the optimal (and
259 *> minimal) LIWORK.
260 *> \endverbatim
261 *>
262 *> \param[in] LIWORK
263 *> \verbatim
264 *> LIWORK is INTEGER
265 *> The dimension of the array IWORK. LIWORK >= max(1,10*N).
266 *>
267 *> If LIWORK = -1, then a workspace query is assumed; the
268 *> routine only calculates the optimal sizes of the WORK and
269 *> IWORK arrays, returns these values as the first entries of
270 *> the WORK and IWORK arrays, and no error message related to
271 *> LWORK or LIWORK is issued by XERBLA.
272 *> \endverbatim
273 *>
274 *> \param[out] INFO
275 *> \verbatim
276 *> INFO is INTEGER
277 *> = 0: successful exit
278 *> < 0: if INFO = -i, the i-th argument had an illegal value
279 *> > 0: Internal error
280 *> \endverbatim
281 *
282 * Authors:
283 * ========
284 *
285 *> \author Univ. of Tennessee
286 *> \author Univ. of California Berkeley
287 *> \author Univ. of Colorado Denver
288 *> \author NAG Ltd.
289 *
290 *> \date June 2016
291 *
292 *> \ingroup doubleOTHEReigen
293 *
294 *> \par Contributors:
295 * ==================
296 *>
297 *> Inderjit Dhillon, IBM Almaden, USA \n
298 *> Osni Marques, LBNL/NERSC, USA \n
299 *> Ken Stanley, Computer Science Division, University of
300 *> California at Berkeley, USA \n
301 *>
302 * =====================================================================
303  SUBROUTINE dstevr( JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL,
304  $ m, w, z, ldz, isuppz, work, lwork, iwork,
305  $ liwork, info )
306 *
307 * -- LAPACK driver routine (version 3.6.1) --
308 * -- LAPACK is a software package provided by Univ. of Tennessee, --
309 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
310 * June 2016
311 *
312 * .. Scalar Arguments ..
313  CHARACTER JOBZ, RANGE
314  INTEGER IL, INFO, IU, LDZ, LIWORK, LWORK, M, N
315  DOUBLE PRECISION ABSTOL, VL, VU
316 * ..
317 * .. Array Arguments ..
318  INTEGER ISUPPZ( * ), IWORK( * )
319  DOUBLE PRECISION D( * ), E( * ), W( * ), WORK( * ), Z( ldz, * )
320 * ..
321 *
322 * =====================================================================
323 *
324 * .. Parameters ..
325  DOUBLE PRECISION ZERO, ONE, TWO
326  parameter ( zero = 0.0d+0, one = 1.0d+0, two = 2.0d+0 )
327 * ..
328 * .. Local Scalars ..
329  LOGICAL ALLEIG, INDEIG, TEST, LQUERY, VALEIG, WANTZ,
330  $ tryrac
331  CHARACTER ORDER
332  INTEGER I, IEEEOK, IMAX, INDIBL, INDIFL, INDISP,
333  $ indiwo, iscale, itmp1, j, jj, liwmin, lwmin,
334  $ nsplit
335  DOUBLE PRECISION BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA, SMLNUM,
336  $ tmp1, tnrm, vll, vuu
337 * ..
338 * .. External Functions ..
339  LOGICAL LSAME
340  INTEGER ILAENV
341  DOUBLE PRECISION DLAMCH, DLANST
342  EXTERNAL lsame, ilaenv, dlamch, dlanst
343 * ..
344 * .. External Subroutines ..
345  EXTERNAL dcopy, dscal, dstebz, dstemr, dstein, dsterf,
346  $ dswap, xerbla
347 * ..
348 * .. Intrinsic Functions ..
349  INTRINSIC max, min, sqrt
350 * ..
351 * .. Executable Statements ..
352 *
353 *
354 * Test the input parameters.
355 *
356  ieeeok = ilaenv( 10, 'DSTEVR', 'N', 1, 2, 3, 4 )
357 *
358  wantz = lsame( jobz, 'V' )
359  alleig = lsame( range, 'A' )
360  valeig = lsame( range, 'V' )
361  indeig = lsame( range, 'I' )
362 *
363  lquery = ( ( lwork.EQ.-1 ) .OR. ( liwork.EQ.-1 ) )
364  lwmin = max( 1, 20*n )
365  liwmin = max( 1, 10*n )
366 *
367 *
368  info = 0
369  IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
370  info = -1
371  ELSE IF( .NOT.( alleig .OR. valeig .OR. indeig ) ) THEN
372  info = -2
373  ELSE IF( n.LT.0 ) THEN
374  info = -3
375  ELSE
376  IF( valeig ) THEN
377  IF( n.GT.0 .AND. vu.LE.vl )
378  $ info = -7
379  ELSE IF( indeig ) THEN
380  IF( il.LT.1 .OR. il.GT.max( 1, n ) ) THEN
381  info = -8
382  ELSE IF( iu.LT.min( n, il ) .OR. iu.GT.n ) THEN
383  info = -9
384  END IF
385  END IF
386  END IF
387  IF( info.EQ.0 ) THEN
388  IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
389  info = -14
390  END IF
391  END IF
392 *
393  IF( info.EQ.0 ) THEN
394  work( 1 ) = lwmin
395  iwork( 1 ) = liwmin
396 *
397  IF( lwork.LT.lwmin .AND. .NOT.lquery ) THEN
398  info = -17
399  ELSE IF( liwork.LT.liwmin .AND. .NOT.lquery ) THEN
400  info = -19
401  END IF
402  END IF
403 *
404  IF( info.NE.0 ) THEN
405  CALL xerbla( 'DSTEVR', -info )
406  RETURN
407  ELSE IF( lquery ) THEN
408  RETURN
409  END IF
410 *
411 * Quick return if possible
412 *
413  m = 0
414  IF( n.EQ.0 )
415  $ RETURN
416 *
417  IF( n.EQ.1 ) THEN
418  IF( alleig .OR. indeig ) THEN
419  m = 1
420  w( 1 ) = d( 1 )
421  ELSE
422  IF( vl.LT.d( 1 ) .AND. vu.GE.d( 1 ) ) THEN
423  m = 1
424  w( 1 ) = d( 1 )
425  END IF
426  END IF
427  IF( wantz )
428  $ z( 1, 1 ) = one
429  RETURN
430  END IF
431 *
432 * Get machine constants.
433 *
434  safmin = dlamch( 'Safe minimum' )
435  eps = dlamch( 'Precision' )
436  smlnum = safmin / eps
437  bignum = one / smlnum
438  rmin = sqrt( smlnum )
439  rmax = min( sqrt( bignum ), one / sqrt( sqrt( safmin ) ) )
440 *
441 *
442 * Scale matrix to allowable range, if necessary.
443 *
444  iscale = 0
445  IF( valeig ) THEN
446  vll = vl
447  vuu = vu
448  END IF
449 *
450  tnrm = dlanst( 'M', n, d, e )
451  IF( tnrm.GT.zero .AND. tnrm.LT.rmin ) THEN
452  iscale = 1
453  sigma = rmin / tnrm
454  ELSE IF( tnrm.GT.rmax ) THEN
455  iscale = 1
456  sigma = rmax / tnrm
457  END IF
458  IF( iscale.EQ.1 ) THEN
459  CALL dscal( n, sigma, d, 1 )
460  CALL dscal( n-1, sigma, e( 1 ), 1 )
461  IF( valeig ) THEN
462  vll = vl*sigma
463  vuu = vu*sigma
464  END IF
465  END IF
466 
467 * Initialize indices into workspaces. Note: These indices are used only
468 * if DSTERF or DSTEMR fail.
469 
470 * IWORK(INDIBL:INDIBL+M-1) corresponds to IBLOCK in DSTEBZ and
471 * stores the block indices of each of the M<=N eigenvalues.
472  indibl = 1
473 * IWORK(INDISP:INDISP+NSPLIT-1) corresponds to ISPLIT in DSTEBZ and
474 * stores the starting and finishing indices of each block.
475  indisp = indibl + n
476 * IWORK(INDIFL:INDIFL+N-1) stores the indices of eigenvectors
477 * that corresponding to eigenvectors that fail to converge in
478 * DSTEIN. This information is discarded; if any fail, the driver
479 * returns INFO > 0.
480  indifl = indisp + n
481 * INDIWO is the offset of the remaining integer workspace.
482  indiwo = indisp + n
483 *
484 * If all eigenvalues are desired, then
485 * call DSTERF or DSTEMR. If this fails for some eigenvalue, then
486 * try DSTEBZ.
487 *
488 *
489  test = .false.
490  IF( indeig ) THEN
491  IF( il.EQ.1 .AND. iu.EQ.n ) THEN
492  test = .true.
493  END IF
494  END IF
495  IF( ( alleig .OR. test ) .AND. ieeeok.EQ.1 ) THEN
496  CALL dcopy( n-1, e( 1 ), 1, work( 1 ), 1 )
497  IF( .NOT.wantz ) THEN
498  CALL dcopy( n, d, 1, w, 1 )
499  CALL dsterf( n, w, work, info )
500  ELSE
501  CALL dcopy( n, d, 1, work( n+1 ), 1 )
502  IF (abstol .LE. two*n*eps) THEN
503  tryrac = .true.
504  ELSE
505  tryrac = .false.
506  END IF
507  CALL dstemr( jobz, 'A', n, work( n+1 ), work, vl, vu, il,
508  $ iu, m, w, z, ldz, n, isuppz, tryrac,
509  $ work( 2*n+1 ), lwork-2*n, iwork, liwork, info )
510 *
511  END IF
512  IF( info.EQ.0 ) THEN
513  m = n
514  GO TO 10
515  END IF
516  info = 0
517  END IF
518 *
519 * Otherwise, call DSTEBZ and, if eigenvectors are desired, DSTEIN.
520 *
521  IF( wantz ) THEN
522  order = 'B'
523  ELSE
524  order = 'E'
525  END IF
526 
527  CALL dstebz( range, order, n, vll, vuu, il, iu, abstol, d, e, m,
528  $ nsplit, w, iwork( indibl ), iwork( indisp ), work,
529  $ iwork( indiwo ), info )
530 *
531  IF( wantz ) THEN
532  CALL dstein( n, d, e, m, w, iwork( indibl ), iwork( indisp ),
533  $ z, ldz, work, iwork( indiwo ), iwork( indifl ),
534  $ info )
535  END IF
536 *
537 * If matrix was scaled, then rescale eigenvalues appropriately.
538 *
539  10 CONTINUE
540  IF( iscale.EQ.1 ) THEN
541  IF( info.EQ.0 ) THEN
542  imax = m
543  ELSE
544  imax = info - 1
545  END IF
546  CALL dscal( imax, one / sigma, w, 1 )
547  END IF
548 *
549 * If eigenvalues are not in order, then sort them, along with
550 * eigenvectors.
551 *
552  IF( wantz ) THEN
553  DO 30 j = 1, m - 1
554  i = 0
555  tmp1 = w( j )
556  DO 20 jj = j + 1, m
557  IF( w( jj ).LT.tmp1 ) THEN
558  i = jj
559  tmp1 = w( jj )
560  END IF
561  20 CONTINUE
562 *
563  IF( i.NE.0 ) THEN
564  itmp1 = iwork( i )
565  w( i ) = w( j )
566  iwork( i ) = iwork( j )
567  w( j ) = tmp1
568  iwork( j ) = itmp1
569  CALL dswap( n, z( 1, i ), 1, z( 1, j ), 1 )
570  END IF
571  30 CONTINUE
572  END IF
573 *
574 * Causes problems with tests 19 & 20:
575 * IF (wantz .and. INDEIG ) Z( 1,1) = Z(1,1) / 1.002 + .002
576 *
577 *
578  work( 1 ) = lwmin
579  iwork( 1 ) = liwmin
580  RETURN
581 *
582 * End of DSTEVR
583 *
584  END
subroutine dsterf(N, D, E, INFO)
DSTERF
Definition: dsterf.f:88
subroutine dstevr(JOBZ, RANGE, N, D, E, VL, VU, IL, IU, ABSTOL, M, W, Z, LDZ, ISUPPZ, WORK, LWORK, IWORK, LIWORK, INFO)
DSTEVR computes the eigenvalues and, optionally, the left and/or right eigenvectors for OTHER matric...
Definition: dstevr.f:306
subroutine dstebz(RANGE, ORDER, N, VL, VU, IL, IU, ABSTOL, D, E, M, NSPLIT, W, IBLOCK, ISPLIT, WORK, IWORK, INFO)
DSTEBZ
Definition: dstebz.f:275
subroutine dcopy(N, DX, INCX, DY, INCY)
DCOPY
Definition: dcopy.f:53
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine dswap(N, DX, INCX, DY, INCY)
DSWAP
Definition: dswap.f:53
subroutine dscal(N, DA, DX, INCX)
DSCAL
Definition: dscal.f:55
subroutine dstemr(JOBZ, RANGE, N, D, E, VL, VU, IL, IU, M, W, Z, LDZ, NZC, ISUPPZ, TRYRAC, WORK, LWORK, IWORK, LIWORK, INFO)
DSTEMR
Definition: dstemr.f:323
subroutine dstein(N, D, E, M, W, IBLOCK, ISPLIT, Z, LDZ, WORK, IWORK, IFAIL, INFO)
DSTEIN
Definition: dstein.f:176