|  | ◆ Dspgvx()
      
        
          | Sub Dspgvx | ( | IType As | Long, |  
          |  |  | Jobz As | String, |  
          |  |  | Range As | String, |  
          |  |  | Uplo As | String, |  
          |  |  | N As | Long, |  
          |  |  | Ap() As | Double, |  
          |  |  | Bp() As | Double, |  
          |  |  | Vl As | Double, |  
          |  |  | Vu As | Double, |  
          |  |  | Il As | Long, |  
          |  |  | Iu As | Long, |  
          |  |  | AbsTol As | Double, |  
          |  |  | M As | Long, |  
          |  |  | W() As | Double, |  
          |  |  | Z() As | Double, |  
          |  |  | IFail() As | Long, |  
          |  |  | Info As | Long |  
          |  | ) |  |  |  
(Expert driver) Generalized eigenvalue problem of symmetric matrices in packed form (expert driver)  PurposeThis routine computes selected eigenvalues, and optionally, the eigenvectors of a real generalized symmetric-definite eigenproblem, of the form Here A and B are assumed to be symmetric, stored in packed form, and B is also positive definite.Ax = λBx, ABx = λx or BAx = λx.Eigenvalues and eigenvectors can be selected by specifying either a range of values or a range of indices for the desired eigenvalues.
 Parameters
  
    | [in] | IType | Specifies the problem type to be solved: = 1: Ax = λBx.
 = 2: ABx = λx.
 = 3: BAx = λx.
 |  | [in] | Jobz | = "N": Compute eigenvalues only. = "V": Compute eigenvalues and eigenvectors.
 |  | [in] | Range | = "A": All eigenvalues will be found. = "V": All eigenvalues in the half-open interval (Vl, Vu] will be found.
 = "I": The Il-th through Iu-th eigenvalues will be found.
 |  | [in] | Uplo | = "U": Upper triangles of A and B are stored. = "L": Lower triangles of A and B are stored.
 |  | [in] | N | Order of the matrices A and B. (N >= 0) (If N = 0, returns without computation) |  | [in,out] | Ap() | Array Ap(LAp - 1) (LAp >= N(N + 1)/2) [in] N x N symmetric matrix A in packed form. The upper or lower triangular part is to be stored in accordance with Uplo.
 [out] The contents of Ap() are destroyed.
 |  | [in,out] | Bp() | Array Bp(LBp - 1) (LBp >= N(N + 1)/2) [in] N x N symmetric positive definite matrix B in packed form. The upper or lower triangular part is to be stored in accordance with Uplo.
 [out] The triangular factor U or L from the Cholesky factorization B = U^T*U or B = L*L^T, in the same storage format as B.
 |  | [in] | Vl | Range = "V": The lower bound of the interval to be searched for eigenvalues. (Vl < Vu) Range = "A" or "I": Not referenced.
 |  | [in] | Vu | Range = "V": The upper bound of the interval to be searched for eigenvalues. (Vl < Vu) Range = "A" or "I": Not referenced.
 |  | [in] | Il | Range = "I": The index of the smallest eigenvalue to be returned. (1 <= Il <= Iu <= N, if N > 0; Il = 1 and Iu = 0 if N = 0) Range = "A" or "V": Not referenced.
 |  | [in] | Iu | Range = "I": The index of the largest eigenvalues to be returned. (1 <= Il <= Iu <= N, if N > 0; Il = 1 and Iu = 0 if N = 0) Range = "A" or "V": Not referenced.
 |  | [in] | AbsTol | The absolute error tolerance for the eigenvalues. An approximate eigenvalue is accepted as converged when it is determined to lie in an interval [a, b] of width less than or equal to AbsTol + eps * max(|a|, |b|), where eps is the machine precision. If AbsTol is less than or equal to zero, then eps*|T| will be used in its place, where |T| is the 1-norm of the tridiagonal matrix obtained by reducing A to tridiagonal form.
 Eigenvalues will be computed most accurately when abstol is set to twice the underflow threshold 2*Dlamch("S"), not zero. If this routine returns with Info > 0, indicating that some eigenvectors did not converge, try setting abstol to 2*Dlamch("S").
 |  | [out] | M | The total number of eigenvalues found. (0 <= M <= N) If Range = "A", M = N, and if Range = "I", M = Iu - Il + 1.
 |  | [out] | W() | Array W(LW - 1) (LW >= N) On normal exit, the first M elements contain the selected eigenvalues in ascending order.
 |  | [out] | Z() | Array Z(LZ1 - 1, LZ2 - 1) (LZ1 >= N, LZ2 >= M) Jobz = "V": If Info = 0, the first M columns of Z() contain the orthonormal eigenvectors of the matrix A corresponding to the selected eigenvalues, with the i-th column of Z() holding the eigenvector associated with W(i).
 The eigenvectors are normalized as follows:
 IType = 1 or 2: Z^T*B*Z = I
 IType = 3: Z^T*inv(B)*Z = I
 If an eigenvector fails to converge, then that column of Z() contains the latest approximation to the eigenvector, and the index of the eigenvector is returned in IFail().
 Jobz = "N": Z() is not referenced.
 Note: The user must ensure that at least max(1, M) columns are supplied in the array Z(); if Range = "V", the exact value of M is not known in advance and an upper bound must be used.
 |  | [out] | IFail() | Array IFail(LIFail - 1) (LIFail >= N) Jobz = "V": If Info = 0, the first M elements of IFail() are zero. If Info > 0, then IFail() contains the indices of the eigenvectors that failed to converge.
 Jobz = "N": IFail() is not referenced.
 |  | [out] | Info | = 0: Successful exit. = -1: The argument Itype had an illegal value. (Itype < 1 or Itype > 3)
 = -2: The argument Jobz had an illegal value. (Jobz <> "V" nor "N")
 = -3: The argument Range had an illegal value. (Range <> "A", "V" nor "I")
 = -4: The argument Uplo had an illegal value. (Uplo <> "U" nor "L")
 = -5: The argument N had an illegal value. (N < 0)
 = -6: The argument Ap() is invalid.
 = -7: The argument Bp() is invalid.
 = -9: The argument Vu had an illegal value. (Vu <= Vl)
 = -10: The argument Il had an illegal value. (Il < 1 or Il > N)
 = -11: The argument Iu had an illegal value. (Iu < min(N, Il) or Iu > N)
 = -14: The argument W() is invalid.
 = -15: The argument Z() is invalid.
 = -16: The argument IFail() is invalid.
 = i (0 < i <= N): Dsyevx failed to converge; i eigenvectors failed to converge. Their indices are stored in array IFail().
 = i (i > N): The leading minor of order i-N of B is not positive definite. The factorization of B could not be completed and no eigenvalues or eigenvectors were computed.
 | 
 ReferenceLAPACK
 Example ProgramCompute the eigenvalues and the eigenvectors of a generalized symmetric-definite eigenproblem of the form Ax = λBx, where A is a symmetric matrix and B is a symmetric positive definite matrix.     (  0.54 -0.90 -0.94 )      (  1.18  0.54 -1.22 )  A = ( -0.90  0.70  1.04 )  B = (  0.54  0.60 -0.71 )     ( -0.94  1.04  1.65 )      ( -1.22 -0.71  1.66 )Sub Ex_Dspgvx()     Const N = 3     Dim Ap(N * (N + 1) / 2) As Double, Bp(N * (N + 1) / 2) As Double     Dim W(N - 1) As Double     Dim Vl As Double, Vu As Double, Il As Long, Iu As Long, AbsTol As Double     Dim M As Long, Z(N - 1, N - 1) As Double, IFail(N - 1) As Long, Info As Long     Ap(0) = 0.54     Ap(1) = -0.9: Ap(3) = 0.7     Ap(2) = -0.94: Ap(4) = 1.04: Ap(5) = 1.65     Bp(0) = 1.18     Bp(1) = 0.54: Bp(3) = 0.6     Bp(2) = -1.22: Bp(4) = -0.71: Bp(5) = 1.66     AbsTol = 0     Call Dspgvx (1, "V", "A", "L", N, Ap(), Bp(), Vl, Vu, Il, Iu, AbsTol, M, W(), Z(), IFail(), Info)    Debug.Print "Eigenvalues =", W(0), W(1), W(2)     Debug.Print "Eigenvectors ="     Debug.Print Z(0, 0), Z(0, 1), Z(0, 2)     Debug.Print Z(1, 0), Z(1, 1), Z(1, 2)     Debug.Print Z(2, 0), Z(2, 1), Z(2, 2)     Debug.Print "M =", M, "Info =", Info End Sub Sub Dspgvx(IType As Long, Jobz As String, Range As String, Uplo As String, N As Long, Ap() As Double, Bp() As Double, Vl As Double, Vu As Double, Il As Long, Iu As Long, AbsTol As Double, M As Long, W() As Double, Z() As Double, IFail() As Long, Info As Long) (Expert driver) Generalized eigenvalue problem of symmetric matrices in packed form (expert driver)
 Example ResultsEigenvalues = -0.297963342573455           0.510423243055614           7.37370278804149  Eigenvectors =  1.17970064313729            1.46384155786189            9.13803098094184E-02   0.497345303675336          -0.442269445774234          -1.71612038711754   0.524910948248221           1.35130854246605           -0.947378600715302  M =            3            Info =         0 
 |