1DGEGS(1) LAPACK driver routine (version 3.2) DGEGS(1)
2
3
4
6 DGEGS - routine i deprecated and has been replaced by routine DGGES
7
9 SUBROUTINE DGEGS( JOBVSL, JOBVSR, N, A, LDA, B, LDB, ALPHAR, ALPHAI,
10 BETA, VSL, LDVSL, VSR, LDVSR, WORK, LWORK, INFO )
11
12 CHARACTER JOBVSL, JOBVSR
13
14 INTEGER INFO, LDA, LDB, LDVSL, LDVSR, LWORK, N
15
16 DOUBLE PRECISION A( LDA, * ), ALPHAI( * ), ALPHAR( * ), B(
17 LDB, * ), BETA( * ), VSL( LDVSL, * ), VSR( LDVSR, *
18 ), WORK( * )
19
21 This routine is deprecated and has been replaced by routine DGGES.
22 DGEGS computes the eigenvalues, real Schur form, and, optionally, left
23 and or/right Schur vectors of a real matrix pair (A,B). Given two
24 square matrices A and B, the generalized real Schur factorization has
25 the form
26 A = Q*S*Z**T, B = Q*T*Z**T
27 where Q and Z are orthogonal matrices, T is upper triangular, and S is
28 an upper quasi-triangular matrix with 1-by-1 and 2-by-2 diagonal
29 blocks, the 2-by-2 blocks corresponding to complex conjugate pairs of
30 eigenvalues of (A,B). The columns of Q are the left Schur vectors and
31 the columns of Z are the right Schur vectors.
32 If only the eigenvalues of (A,B) are needed, the driver routine DGEGV
33 should be used instead. See DGEGV for a description of the eigenvalues
34 of the generalized nonsymmetric eigenvalue problem (GNEP).
35
37 JOBVSL (input) CHARACTER*1
38 = 'N': do not compute the left Schur vectors;
39 = 'V': compute the left Schur vectors (returned in VSL).
40
41 JOBVSR (input) CHARACTER*1
42 = 'N': do not compute the right Schur vectors;
43 = 'V': compute the right Schur vectors (returned in VSR).
44
45 N (input) INTEGER
46 The order of the matrices A, B, VSL, and VSR. N >= 0.
47
48 A (input/output) DOUBLE PRECISION array, dimension (LDA, N)
49 On entry, the matrix A. On exit, the upper quasi-triangular
50 matrix S from the generalized real Schur factorization.
51
52 LDA (input) INTEGER
53 The leading dimension of A. LDA >= max(1,N).
54
55 B (input/output) DOUBLE PRECISION array, dimension (LDB, N)
56 On entry, the matrix B. On exit, the upper triangular matrix T
57 from the generalized real Schur factorization.
58
59 LDB (input) INTEGER
60 The leading dimension of B. LDB >= max(1,N).
61
62 ALPHAR (output) DOUBLE PRECISION array, dimension (N)
63 The real parts of each scalar alpha defining an eigenvalue of
64 GNEP.
65
66 ALPHAI (output) DOUBLE PRECISION array, dimension (N)
67 The imaginary parts of each scalar alpha defining an eigenvalue
68 of GNEP. If ALPHAI(j) is zero, then the j-th eigenvalue is
69 real; if positive, then the j-th and (j+1)-st eigenvalues are a
70 complex conjugate pair, with ALPHAI(j+1) = -ALPHAI(j).
71
72 BETA (output) DOUBLE PRECISION array, dimension (N)
73 The scalars beta that define the eigenvalues of GNEP.
74 Together, the quantities alpha = (ALPHAR(j),ALPHAI(j)) and beta
75 = BETA(j) represent the j-th eigenvalue of the matrix pair
76 (A,B), in one of the forms lambda = alpha/beta or mu =
77 beta/alpha. Since either lambda or mu may overflow, they
78 should not, in general, be computed.
79
80 VSL (output) DOUBLE PRECISION array, dimension (LDVSL,N)
81 If JOBVSL = 'V', the matrix of left Schur vectors Q. Not ref‐
82 erenced if JOBVSL = 'N'.
83
84 LDVSL (input) INTEGER
85 The leading dimension of the matrix VSL. LDVSL >=1, and if JOB‐
86 VSL = 'V', LDVSL >= N.
87
88 VSR (output) DOUBLE PRECISION array, dimension (LDVSR,N)
89 If JOBVSR = 'V', the matrix of right Schur vectors Z. Not ref‐
90 erenced if JOBVSR = 'N'.
91
92 LDVSR (input) INTEGER
93 The leading dimension of the matrix VSR. LDVSR >= 1, and if
94 JOBVSR = 'V', LDVSR >= N.
95
96 WORK (workspace/output) DOUBLE PRECISION array, dimension
97 (MAX(1,LWORK))
98 On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
99
100 LWORK (input) INTEGER
101 The dimension of the array WORK. LWORK >= max(1,4*N). For
102 good performance, LWORK must generally be larger. To compute
103 the optimal value of LWORK, call ILAENV to get blocksizes (for
104 DGEQRF, DORMQR, and DORGQR.) Then compute: NB -- MAX of the
105 blocksizes for DGEQRF, DORMQR, and DORGQR The optimal LWORK is
106 2*N + N*(NB+1). If LWORK = -1, then a workspace query is
107 assumed; the routine only calculates the optimal size of the
108 WORK array, returns this value as the first entry of the WORK
109 array, and no error message related to LWORK is issued by
110 XERBLA.
111
112 INFO (output) INTEGER
113 = 0: successful exit
114 < 0: if INFO = -i, the i-th argument had an illegal value.
115 = 1,...,N: The QZ iteration failed. (A,B) are not in Schur
116 form, but ALPHAR(j), ALPHAI(j), and BETA(j) should be correct
117 for j=INFO+1,...,N. > N: errors that usually indicate LAPACK
118 problems:
119 =N+1: error return from DGGBAL
120 =N+2: error return from DGEQRF
121 =N+3: error return from DORMQR
122 =N+4: error return from DORGQR
123 =N+5: error return from DGGHRD
124 =N+6: error return from DHGEQZ (other than failed iteration)
125 =N+7: error return from DGGBAK (computing VSL)
126 =N+8: error return from DGGBAK (computing VSR)
127 =N+9: error return from DLASCL (various places)
128
129
130
131 LAPACK driver routine (version 3.N2o)vember 2008 DGEGS(1)