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