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

NAME

6       DSPGVD  -  all  the  eigenvalues, and optionally, the eigenvectors of a
7       real  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 DSPGVD( ITYPE,  JOBZ,  UPLO,  N,  AP,  BP,  W, Z, LDZ, WORK,
12                          LWORK, IWORK, LIWORK, INFO )
13
14           CHARACTER      JOBZ, UPLO
15
16           INTEGER        INFO, ITYPE, LDZ, LIWORK, LWORK, N
17
18           INTEGER        IWORK( * )
19
20           DOUBLE         PRECISION AP( * ), BP( * ), W( * ), WORK(  *  ),  Z(
21                          LDZ, * )
22

PURPOSE

24       DSPGVD  computes  all the eigenvalues, and optionally, the eigenvectors
25       of a real generalized  symmetric-definite  eigenproblem,  of  the  form
26       A*x=(lambda)*B*x,  A*Bx=(lambda)*x,  or B*A*x=(lambda)*x.  Here A and B
27       are assumed to be symmetric, stored in packed format,  and  B  is  also
28       positive definite.
29       If eigenvectors are desired, it uses a divide and conquer algorithm.
30
31       The  divide  and  conquer  algorithm  makes very mild assumptions about
32       floating point arithmetic. It will work on machines with a guard  digit
33       in add/subtract, or on those binary machines without guard digits which
34       subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or Cray-2. It  could
35       conceivably  fail on hexadecimal or decimal machines without guard dig‐
36       its, but we know of none.
37
38

ARGUMENTS

40       ITYPE   (input) INTEGER
41               Specifies the problem type to be solved:
42               = 1:  A*x = (lambda)*B*x
43               = 2:  A*B*x = (lambda)*x
44               = 3:  B*A*x = (lambda)*x
45
46       JOBZ    (input) CHARACTER*1
47               = 'N':  Compute eigenvalues only;
48               = 'V':  Compute eigenvalues and eigenvectors.
49
50       UPLO    (input) CHARACTER*1
51               = 'U':  Upper triangles of A and B are stored;
52               = 'L':  Lower triangles of A and B are stored.
53
54       N       (input) INTEGER
55               The order of the matrices A and B.  N >= 0.
56
57       AP      (input/output) DOUBLE PRECISION array, dimension (N*(N+1)/2)
58               On entry, the upper or lower triangle of the  symmetric  matrix
59               A,  packed  columnwise in a linear array.  The j-th column of A
60               is stored in the array AP as follows: if UPLO  =  'U',  AP(i  +
61               (j-1)*j/2)  =  A(i,j)  for  1<=i<=j;  if  UPLO  =  'L',  AP(i +
62               (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n.
63
64               On exit, the contents of AP are destroyed.
65
66       BP      (input/output) DOUBLE PRECISION array, dimension (N*(N+1)/2)
67               On entry, the upper or lower triangle of the  symmetric  matrix
68               B,  packed  columnwise in a linear array.  The j-th column of B
69               is stored in the array BP as follows: if UPLO  =  'U',  BP(i  +
70               (j-1)*j/2)  =  B(i,j)  for  1<=i<=j;  if  UPLO  =  'L',  BP(i +
71               (j-1)*(2*n-j)/2) = B(i,j) for j<=i<=n.
72
73               On exit, the triangular factor U or L from the Cholesky factor‐
74               ization B = U**T*U or B = L*L**T, in the same storage format as
75               B.
76
77       W       (output) DOUBLE PRECISION array, dimension (N)
78               If INFO = 0, the eigenvalues in ascending order.
79
80       Z       (output) DOUBLE PRECISION array, dimension (LDZ, N)
81               If JOBZ = 'V', then if INFO = 0, Z contains  the  matrix  Z  of
82               eigenvectors.   The  eigenvectors are normalized as follows: if
83               ITYPE = 1 or 2, Z**T*B*Z = I; if ITYPE = 3, Z**T*inv(B)*Z =  I.
84               If JOBZ = 'N', then Z is not referenced.
85
86       LDZ     (input) INTEGER
87               The  leading dimension of the array Z.  LDZ >= 1, and if JOBZ =
88               'V', LDZ >= max(1,N).
89
90       WORK      (workspace/output)   DOUBLE   PRECISION   array,    dimension
91       (MAX(1,LWORK))
92               On exit, if INFO = 0, WORK(1) returns the required LWORK.
93
94       LWORK   (input) INTEGER
95               The    dimension   of   the   array   WORK.    If   N   <=   1,
96               LWORK >= 1.  If JOBZ = 'N' and N > 1, LWORK >= 2*N.  If JOBZ  =
97               'V' and N > 1, LWORK >= 1 + 6*N + 2*N**2.
98
99               If  LWORK  = -1, then a workspace query is assumed; the routine
100               only calculates the  required  sizes  of  the  WORK  and  IWORK
101               arrays,  returns  these values as the first entries of the WORK
102               and IWORK arrays, and no error  message  related  to  LWORK  or
103               LIWORK is issued by XERBLA.
104
105       IWORK   (workspace/output) INTEGER array, dimension (MAX(1,LIWORK))
106               On exit, if INFO = 0, IWORK(1) returns the required LIWORK.
107
108       LIWORK  (input) INTEGER
109               The  dimension  of  the array IWORK.  If JOBZ  = 'N' or N <= 1,
110               LIWORK >= 1.  If JOBZ  = 'V' and N > 1, LIWORK >= 3 + 5*N.
111
112               If LIWORK = -1, then a workspace query is assumed; the  routine
113               only  calculates  the  required  sizes  of  the  WORK and IWORK
114               arrays, returns these values as the first entries of  the  WORK
115               and  IWORK  arrays,  and  no  error message related to LWORK or
116               LIWORK is issued by XERBLA.
117
118       INFO    (output) INTEGER
119               = 0:  successful exit
120               < 0:  if INFO = -i, the i-th argument had an illegal value
121               > 0:  DPPTRF or DSPEVD returned an error code:
122               <= N:  if INFO = i, DSPEVD failed to converge;  i  off-diagonal
123               elements  of  an intermediate tridiagonal form did not converge
124               to zero; > N:   if INFO = N + i, for 1 <=  i  <=  N,  then  the
125               leading  minor  of  order i of B is not positive definite.  The
126               factorization of B could not be completed and no eigenvalues or
127               eigenvectors were computed.
128

FURTHER DETAILS

130       Based on contributions by
131          Mark Fahey, Department of Mathematics, Univ. of Kentucky, USA
132
133
134
135
136 LAPACK driver routine (version 3.N1o)vember 2006                       DSPGVD(1)
Impressum