LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
ssbev.f
Go to the documentation of this file.
1 *> \brief <b> SSBEV 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 SSBEV + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssbev.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssbev.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssbev.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE SSBEV( JOBZ, UPLO, N, KD, AB, LDAB, W, Z, LDZ, WORK,
22 * INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER JOBZ, UPLO
26 * INTEGER INFO, KD, LDAB, LDZ, N
27 * ..
28 * .. Array Arguments ..
29 * REAL AB( LDAB, * ), W( * ), WORK( * ), Z( LDZ, * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> SSBEV computes all the eigenvalues and, optionally, eigenvectors of
39 *> a real symmetric band matrix A.
40 *> \endverbatim
41 *
42 * Arguments:
43 * ==========
44 *
45 *> \param[in] JOBZ
46 *> \verbatim
47 *> JOBZ is CHARACTER*1
48 *> = 'N': Compute eigenvalues only;
49 *> = 'V': Compute eigenvalues and eigenvectors.
50 *> \endverbatim
51 *>
52 *> \param[in] UPLO
53 *> \verbatim
54 *> UPLO is CHARACTER*1
55 *> = 'U': Upper triangle of A is stored;
56 *> = 'L': Lower triangle of A is stored.
57 *> \endverbatim
58 *>
59 *> \param[in] N
60 *> \verbatim
61 *> N is INTEGER
62 *> The order of the matrix A. N >= 0.
63 *> \endverbatim
64 *>
65 *> \param[in] KD
66 *> \verbatim
67 *> KD is INTEGER
68 *> The number of superdiagonals of the matrix A if UPLO = 'U',
69 *> or the number of subdiagonals if UPLO = 'L'. KD >= 0.
70 *> \endverbatim
71 *>
72 *> \param[in,out] AB
73 *> \verbatim
74 *> AB is REAL array, dimension (LDAB, N)
75 *> On entry, the upper or lower triangle of the symmetric band
76 *> matrix A, stored in the first KD+1 rows of the array. The
77 *> j-th column of A is stored in the j-th column of the array AB
78 *> as follows:
79 *> if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
80 *> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
81 *>
82 *> On exit, AB is overwritten by values generated during the
83 *> reduction to tridiagonal form. If UPLO = 'U', the first
84 *> superdiagonal and the diagonal of the tridiagonal matrix T
85 *> are returned in rows KD and KD+1 of AB, and if UPLO = 'L',
86 *> the diagonal and first subdiagonal of T are returned in the
87 *> first two rows of AB.
88 *> \endverbatim
89 *>
90 *> \param[in] LDAB
91 *> \verbatim
92 *> LDAB is INTEGER
93 *> The leading dimension of the array AB. LDAB >= KD + 1.
94 *> \endverbatim
95 *>
96 *> \param[out] W
97 *> \verbatim
98 *> W is REAL array, dimension (N)
99 *> If INFO = 0, the eigenvalues in ascending order.
100 *> \endverbatim
101 *>
102 *> \param[out] Z
103 *> \verbatim
104 *> Z is REAL array, dimension (LDZ, N)
105 *> If JOBZ = 'V', then if INFO = 0, Z contains the orthonormal
106 *> eigenvectors of the matrix A, with the i-th column of Z
107 *> holding the eigenvector associated with W(i).
108 *> If JOBZ = 'N', then Z is not referenced.
109 *> \endverbatim
110 *>
111 *> \param[in] LDZ
112 *> \verbatim
113 *> LDZ is INTEGER
114 *> The leading dimension of the array Z. LDZ >= 1, and if
115 *> JOBZ = 'V', LDZ >= max(1,N).
116 *> \endverbatim
117 *>
118 *> \param[out] WORK
119 *> \verbatim
120 *> WORK is REAL array, dimension (max(1,3*N-2))
121 *> \endverbatim
122 *>
123 *> \param[out] INFO
124 *> \verbatim
125 *> INFO is INTEGER
126 *> = 0: successful exit
127 *> < 0: if INFO = -i, the i-th argument had an illegal value
128 *> > 0: if INFO = i, the algorithm failed to converge; i
129 *> off-diagonal elements of an intermediate tridiagonal
130 *> form did not converge to zero.
131 *> \endverbatim
132 *
133 * Authors:
134 * ========
135 *
136 *> \author Univ. of Tennessee
137 *> \author Univ. of California Berkeley
138 *> \author Univ. of Colorado Denver
139 *> \author NAG Ltd.
140 *
141 *> \date November 2011
142 *
143 *> \ingroup realOTHEReigen
144 *
145 * =====================================================================
146  SUBROUTINE ssbev( JOBZ, UPLO, N, KD, AB, LDAB, W, Z, LDZ, WORK,
147  $ info )
148 *
149 * -- LAPACK driver routine (version 3.4.0) --
150 * -- LAPACK is a software package provided by Univ. of Tennessee, --
151 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
152 * November 2011
153 *
154 * .. Scalar Arguments ..
155  CHARACTER jobz, uplo
156  INTEGER info, kd, ldab, ldz, n
157 * ..
158 * .. Array Arguments ..
159  REAL ab( ldab, * ), w( * ), work( * ), z( ldz, * )
160 * ..
161 *
162 * =====================================================================
163 *
164 * .. Parameters ..
165  REAL zero, one
166  parameter( zero = 0.0e0, one = 1.0e0 )
167 * ..
168 * .. Local Scalars ..
169  LOGICAL lower, wantz
170  INTEGER iinfo, imax, inde, indwrk, iscale
171  REAL anrm, bignum, eps, rmax, rmin, safmin, sigma,
172  $ smlnum
173 * ..
174 * .. External Functions ..
175  LOGICAL lsame
176  REAL slamch, slansb
177  EXTERNAL lsame, slamch, slansb
178 * ..
179 * .. External Subroutines ..
180  EXTERNAL slascl, ssbtrd, sscal, ssteqr, ssterf, xerbla
181 * ..
182 * .. Intrinsic Functions ..
183  INTRINSIC sqrt
184 * ..
185 * .. Executable Statements ..
186 *
187 * Test the input parameters.
188 *
189  wantz = lsame( jobz, 'V' )
190  lower = lsame( uplo, 'L' )
191 *
192  info = 0
193  IF( .NOT.( wantz .OR. lsame( jobz, 'N' ) ) ) THEN
194  info = -1
195  ELSE IF( .NOT.( lower .OR. lsame( uplo, 'U' ) ) ) THEN
196  info = -2
197  ELSE IF( n.LT.0 ) THEN
198  info = -3
199  ELSE IF( kd.LT.0 ) THEN
200  info = -4
201  ELSE IF( ldab.LT.kd+1 ) THEN
202  info = -6
203  ELSE IF( ldz.LT.1 .OR. ( wantz .AND. ldz.LT.n ) ) THEN
204  info = -9
205  END IF
206 *
207  IF( info.NE.0 ) THEN
208  CALL xerbla( 'SSBEV ', -info )
209  return
210  END IF
211 *
212 * Quick return if possible
213 *
214  IF( n.EQ.0 )
215  $ return
216 *
217  IF( n.EQ.1 ) THEN
218  IF( lower ) THEN
219  w( 1 ) = ab( 1, 1 )
220  ELSE
221  w( 1 ) = ab( kd+1, 1 )
222  END IF
223  IF( wantz )
224  $ z( 1, 1 ) = one
225  return
226  END IF
227 *
228 * Get machine constants.
229 *
230  safmin = slamch( 'Safe minimum' )
231  eps = slamch( 'Precision' )
232  smlnum = safmin / eps
233  bignum = one / smlnum
234  rmin = sqrt( smlnum )
235  rmax = sqrt( bignum )
236 *
237 * Scale matrix to allowable range, if necessary.
238 *
239  anrm = slansb( 'M', uplo, n, kd, ab, ldab, work )
240  iscale = 0
241  IF( anrm.GT.zero .AND. anrm.LT.rmin ) THEN
242  iscale = 1
243  sigma = rmin / anrm
244  ELSE IF( anrm.GT.rmax ) THEN
245  iscale = 1
246  sigma = rmax / anrm
247  END IF
248  IF( iscale.EQ.1 ) THEN
249  IF( lower ) THEN
250  CALL slascl( 'B', kd, kd, one, sigma, n, n, ab, ldab, info )
251  ELSE
252  CALL slascl( 'Q', kd, kd, one, sigma, n, n, ab, ldab, info )
253  END IF
254  END IF
255 *
256 * Call SSBTRD to reduce symmetric band matrix to tridiagonal form.
257 *
258  inde = 1
259  indwrk = inde + n
260  CALL ssbtrd( jobz, uplo, n, kd, ab, ldab, w, work( inde ), z, ldz,
261  $ work( indwrk ), iinfo )
262 *
263 * For eigenvalues only, call SSTERF. For eigenvectors, call SSTEQR.
264 *
265  IF( .NOT.wantz ) THEN
266  CALL ssterf( n, w, work( inde ), info )
267  ELSE
268  CALL ssteqr( jobz, n, w, work( inde ), z, ldz, work( indwrk ),
269  $ info )
270  END IF
271 *
272 * If matrix was scaled, then rescale eigenvalues appropriately.
273 *
274  IF( iscale.EQ.1 ) THEN
275  IF( info.EQ.0 ) THEN
276  imax = n
277  ELSE
278  imax = info - 1
279  END IF
280  CALL sscal( imax, one / sigma, w, 1 )
281  END IF
282 *
283  return
284 *
285 * End of SSBEV
286 *
287  END