1SSYGVX(1)             LAPACK driver routine (version 3.1)            SSYGVX(1)
2
3
4

NAME

6       SSYGVX  -  selected eigenvalues, and optionally, eigenvectors of a real
7       generalized    symmetric-definite    eigenproblem,    of    the    form
8       A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x=(lambda)*x
9

SYNOPSIS

11       SUBROUTINE SSYGVX( ITYPE, JOBZ, RANGE, UPLO, N, A, LDA, B, LDB, VL, VU,
12                          IL, IU, ABSTOL, M, W, Z, LDZ,  WORK,  LWORK,  IWORK,
13                          IFAIL, INFO )
14
15           CHARACTER      JOBZ, RANGE, UPLO
16
17           INTEGER        IL, INFO, ITYPE, IU, LDA, LDB, LDZ, LWORK, M, N
18
19           REAL           ABSTOL, VL, VU
20
21           INTEGER        IFAIL( * ), IWORK( * )
22
23           REAL           A( LDA, * ), B( LDB, * ), W( * ), WORK( * ), Z( LDZ,
24                          * )
25

PURPOSE

27       SSYGVX computes selected eigenvalues, and optionally, eigenvectors of a
28       real   generalized   symmetric-definite   eigenproblem,   of  the  form
29       A*x=(lambda)*B*x,  A*Bx=(lambda)*x,  or B*A*x=(lambda)*x.  Here A and B
30       are assumed to be symmetric and B is also positive definite.  Eigenval‐
31       ues and eigenvectors can be selected by specifying either  a  range  of
32       values or a range of indices for the desired eigenvalues.
33
34

ARGUMENTS

36       ITYPE   (input) INTEGER
37               Specifies the problem type to be solved:
38               = 1:  A*x = (lambda)*B*x
39               = 2:  A*B*x = (lambda)*x
40               = 3:  B*A*x = (lambda)*x
41
42       JOBZ    (input) CHARACTER*1
43               = 'N':  Compute eigenvalues only;
44               = 'V':  Compute eigenvalues and eigenvectors.
45
46       RANGE   (input) CHARACTER*1
47               = 'A': all eigenvalues will be found.
48               =  'V':  all eigenvalues in the half-open interval (VL,VU] will
49               be found.  = 'I': the IL-th through IU-th eigenvalues  will  be
50               found.
51
52       UPLO    (input) CHARACTER*1
53               = 'U':  Upper triangle of A and B are stored;
54               = 'L':  Lower triangle of A and B are stored.
55
56       N       (input) INTEGER
57               The order of the matrix pencil (A,B).  N >= 0.
58
59       A       (input/output) REAL array, dimension (LDA, N)
60               On  entry,  the symmetric matrix A.  If UPLO = 'U', the leading
61               N-by-N upper triangular part of A contains the upper triangular
62               part  of the matrix A.  If UPLO = 'L', the leading N-by-N lower
63               triangular part of A contains the lower triangular part of  the
64               matrix A.
65
66               On exit, the lower triangle (if UPLO='L') or the upper triangle
67               (if UPLO='U') of A, including the diagonal, is destroyed.
68
69       LDA     (input) INTEGER
70               The leading dimension of the array A.  LDA >= max(1,N).
71
72       B       (input/output) REAL array, dimension (LDA, N)
73               On entry, the symmetric matrix B.  If UPLO = 'U',  the  leading
74               N-by-N upper triangular part of B contains the upper triangular
75               part of the matrix B.  If UPLO = 'L', the leading N-by-N  lower
76               triangular  part of B contains the lower triangular part of the
77               matrix B.
78
79               On exit, if INFO <= N, the part of B containing the  matrix  is
80               overwritten  by  the triangular factor U or L from the Cholesky
81               factorization B = U**T*U or B = L*L**T.
82
83       LDB     (input) INTEGER
84               The leading dimension of the array B.  LDB >= max(1,N).
85
86       VL      (input) REAL
87               VU      (input) REAL If RANGE='V', the lower and  upper  bounds
88               of  the  interval to be searched for eigenvalues. VL < VU.  Not
89               referenced if RANGE = 'A' or 'I'.
90
91       IL      (input) INTEGER
92               IU      (input) INTEGER If RANGE='I', the indices (in ascending
93               order)  of the smallest and largest eigenvalues to be returned.
94               1 <= IL <= IU <= N, if N > 0; IL = 1 and IU = 0 if N = 0.   Not
95               referenced if RANGE = 'A' or 'V'.
96
97       ABSTOL  (input) REAL
98               The  absolute error tolerance for the eigenvalues.  An approxi‐
99               mate eigenvalue is accepted as converged when it is  determined
100               to lie in an interval [a,b] of width less than or equal to
101
102               ABSTOL + EPS *   max( |a|,|b| ) ,
103
104               where  EPS is the machine precision.  If ABSTOL is less than or
105               equal to zero, then  EPS*|T|  will be used in its place,  where
106               |T|  is the 1-norm of the tridiagonal matrix obtained by reduc‐
107               ing A to tridiagonal form.
108
109               Eigenvalues will be computed most accurately when ABSTOL is set
110               to  twice  the underflow threshold 2*DLAMCH('S'), not zero.  If
111               this routine returns with INFO>0, indicating that  some  eigen‐
112               vectors did not converge, try setting ABSTOL to 2*SLAMCH('S').
113
114       M       (output) INTEGER
115               The  total number of eigenvalues found.  0 <= M <= N.  If RANGE
116               = 'A', M = N, and if RANGE = 'I', M = IU-IL+1.
117
118       W       (output) REAL array, dimension (N)
119               On normal exit, the first M elements contain the  selected  ei‐
120               genvalues in ascending order.
121
122       Z       (output) REAL array, dimension (LDZ, max(1,M))
123               If  JOBZ  = 'N', then Z is not referenced.  If JOBZ = 'V', then
124               if INFO = 0, the first M columns of Z contain  the  orthonormal
125               eigenvectors  of the matrix A corresponding to the selected ei‐
126               genvalues, with the i-th column of Z  holding  the  eigenvector
127               associated  with W(i).  The eigenvectors are normalized as fol‐
128               lows: if ITYPE  =  1  or  2,  Z**T*B*Z  =  I;  if  ITYPE  =  3,
129               Z**T*inv(B)*Z = I.
130
131               If an eigenvector fails to converge, then that column of Z con‐
132               tains the latest approximation  to  the  eigenvector,  and  the
133               index  of the eigenvector is returned in IFAIL.  Note: the user
134               must ensure that at least max(1,M) columns are supplied in  the
135               array  Z;  if RANGE = 'V', the exact value of M is not known in
136               advance and an upper bound must be used.
137
138       LDZ     (input) INTEGER
139               The leading dimension of the array Z.  LDZ >= 1, and if JOBZ  =
140               'V', LDZ >= max(1,N).
141
142       WORK    (workspace/output) REAL array, dimension (MAX(1,LWORK))
143               On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
144
145       LWORK   (input) INTEGER
146               The  length of the array WORK.  LWORK >= max(1,8*N).  For opti‐
147               mal efficiency, LWORK >= (NB+3)*N, where NB  is  the  blocksize
148               for SSYTRD returned by ILAENV.
149
150               If  LWORK  = -1, then a workspace query is assumed; the routine
151               only calculates the optimal size of  the  WORK  array,  returns
152               this  value  as the first entry of the WORK array, and no error
153               message related to LWORK is issued by XERBLA.
154
155       IWORK   (workspace) INTEGER array, dimension (5*N)
156
157       IFAIL   (output) INTEGER array, dimension (N)
158               If JOBZ = 'V', then if INFO = 0, the first M elements of  IFAIL
159               are  zero.  If INFO > 0, then IFAIL contains the indices of the
160               eigenvectors that failed to converge.   If  JOBZ  =  'N',  then
161               IFAIL is not referenced.
162
163       INFO    (output) INTEGER
164               = 0:  successful exit
165               < 0:  if INFO = -i, the i-th argument had an illegal value
166               > 0:  SPOTRF or SSYEVX returned an error code:
167               <=  N:   if INFO = i, SSYEVX failed to converge; i eigenvectors
168               failed to converge.  Their indices are stored in  array  IFAIL.
169               > N:   if INFO = N + i, for 1 <= i <= N, then the leading minor
170               of order i of B is not positive definite.  The factorization of
171               B  could  not  be  completed and no eigenvalues or eigenvectors
172               were computed.
173

FURTHER DETAILS

175       Based on contributions by
176          Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA
177
178
179
180
181 LAPACK driver routine (version 3.N1o)vember 2006                       SSYGVX(1)
Impressum