LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ztgexc.f
Go to the documentation of this file.
1*> \brief \b ZTGEXC
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download ZTGEXC + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztgexc.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztgexc.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgexc.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE ZTGEXC( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
20* LDZ, IFST, ILST, INFO )
21*
22* .. Scalar Arguments ..
23* LOGICAL WANTQ, WANTZ
24* INTEGER IFST, ILST, INFO, LDA, LDB, LDQ, LDZ, N
25* ..
26* .. Array Arguments ..
27* COMPLEX*16 A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
28* $ Z( LDZ, * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> ZTGEXC reorders the generalized Schur decomposition of a complex
38*> matrix pair (A,B), using an unitary equivalence transformation
39*> (A, B) := Q * (A, B) * Z**H, so that the diagonal block of (A, B) with
40*> row index IFST is moved to row ILST.
41*>
42*> (A, B) must be in generalized Schur canonical form, that is, A and
43*> B are both upper triangular.
44*>
45*> Optionally, the matrices Q and Z of generalized Schur vectors are
46*> updated.
47*>
48*> Q(in) * A(in) * Z(in)**H = Q(out) * A(out) * Z(out)**H
49*> Q(in) * B(in) * Z(in)**H = Q(out) * B(out) * Z(out)**H
50*> \endverbatim
51*
52* Arguments:
53* ==========
54*
55*> \param[in] WANTQ
56*> \verbatim
57*> WANTQ is LOGICAL
58*> .TRUE. : update the left transformation matrix Q;
59*> .FALSE.: do not update Q.
60*> \endverbatim
61*>
62*> \param[in] WANTZ
63*> \verbatim
64*> WANTZ is LOGICAL
65*> .TRUE. : update the right transformation matrix Z;
66*> .FALSE.: do not update Z.
67*> \endverbatim
68*>
69*> \param[in] N
70*> \verbatim
71*> N is INTEGER
72*> The order of the matrices A and B. N >= 0.
73*> \endverbatim
74*>
75*> \param[in,out] A
76*> \verbatim
77*> A is COMPLEX*16 array, dimension (LDA,N)
78*> On entry, the upper triangular matrix A in the pair (A, B).
79*> On exit, the updated matrix A.
80*> \endverbatim
81*>
82*> \param[in] LDA
83*> \verbatim
84*> LDA is INTEGER
85*> The leading dimension of the array A. LDA >= max(1,N).
86*> \endverbatim
87*>
88*> \param[in,out] B
89*> \verbatim
90*> B is COMPLEX*16 array, dimension (LDB,N)
91*> On entry, the upper triangular matrix B in the pair (A, B).
92*> On exit, the updated matrix B.
93*> \endverbatim
94*>
95*> \param[in] LDB
96*> \verbatim
97*> LDB is INTEGER
98*> The leading dimension of the array B. LDB >= max(1,N).
99*> \endverbatim
100*>
101*> \param[in,out] Q
102*> \verbatim
103*> Q is COMPLEX*16 array, dimension (LDQ,N)
104*> On entry, if WANTQ = .TRUE., the unitary matrix Q.
105*> On exit, the updated matrix Q.
106*> If WANTQ = .FALSE., Q is not referenced.
107*> \endverbatim
108*>
109*> \param[in] LDQ
110*> \verbatim
111*> LDQ is INTEGER
112*> The leading dimension of the array Q. LDQ >= 1;
113*> If WANTQ = .TRUE., LDQ >= N.
114*> \endverbatim
115*>
116*> \param[in,out] Z
117*> \verbatim
118*> Z is COMPLEX*16 array, dimension (LDZ,N)
119*> On entry, if WANTZ = .TRUE., the unitary matrix Z.
120*> On exit, the updated matrix Z.
121*> If WANTZ = .FALSE., Z is not referenced.
122*> \endverbatim
123*>
124*> \param[in] LDZ
125*> \verbatim
126*> LDZ is INTEGER
127*> The leading dimension of the array Z. LDZ >= 1;
128*> If WANTZ = .TRUE., LDZ >= N.
129*> \endverbatim
130*>
131*> \param[in] IFST
132*> \verbatim
133*> IFST is INTEGER
134*> \endverbatim
135*>
136*> \param[in,out] ILST
137*> \verbatim
138*> ILST is INTEGER
139*> Specify the reordering of the diagonal blocks of (A, B).
140*> The block with row index IFST is moved to row ILST, by a
141*> sequence of swapping between adjacent blocks.
142*> \endverbatim
143*>
144*> \param[out] INFO
145*> \verbatim
146*> INFO is INTEGER
147*> =0: Successful exit.
148*> <0: if INFO = -i, the i-th argument had an illegal value.
149*> =1: The transformed matrix pair (A, B) would be too far
150*> from generalized Schur form; the problem is ill-
151*> conditioned. (A, B) may have been partially reordered,
152*> and ILST points to the first row of the current
153*> position of the block being moved.
154*> \endverbatim
155*
156* Authors:
157* ========
158*
159*> \author Univ. of Tennessee
160*> \author Univ. of California Berkeley
161*> \author Univ. of Colorado Denver
162*> \author NAG Ltd.
163*
164*> \ingroup tgexc
165*
166*> \par Contributors:
167* ==================
168*>
169*> Bo Kagstrom and Peter Poromaa, Department of Computing Science,
170*> Umea University, S-901 87 Umea, Sweden.
171*
172*> \par References:
173* ================
174*>
175*> [1] B. Kagstrom; A Direct Method for Reordering Eigenvalues in the
176*> Generalized Real Schur Form of a Regular Matrix Pair (A, B), in
177*> M.S. Moonen et al (eds), Linear Algebra for Large Scale and
178*> Real-Time Applications, Kluwer Academic Publ. 1993, pp 195-218.
179*> \n
180*> [2] B. Kagstrom and P. Poromaa; Computing Eigenspaces with Specified
181*> Eigenvalues of a Regular Matrix Pair (A, B) and Condition
182*> Estimation: Theory, Algorithms and Software, Report
183*> UMINF - 94.04, Department of Computing Science, Umea University,
184*> S-901 87 Umea, Sweden, 1994. Also as LAPACK Working Note 87.
185*> To appear in Numerical Algorithms, 1996.
186*> \n
187*> [3] B. Kagstrom and P. Poromaa, LAPACK-Style Algorithms and Software
188*> for Solving the Generalized Sylvester Equation and Estimating the
189*> Separation between Regular Matrix Pairs, Report UMINF - 93.23,
190*> Department of Computing Science, Umea University, S-901 87 Umea,
191*> Sweden, December 1993, Revised April 1994, Also as LAPACK working
192*> Note 75. To appear in ACM Trans. on Math. Software, Vol 22, No 1,
193*> 1996.
194*>
195* =====================================================================
196 SUBROUTINE ztgexc( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
197 $ LDZ, IFST, ILST, INFO )
198*
199* -- LAPACK computational routine --
200* -- LAPACK is a software package provided by Univ. of Tennessee, --
201* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
202*
203* .. Scalar Arguments ..
204 LOGICAL WANTQ, WANTZ
205 INTEGER IFST, ILST, INFO, LDA, LDB, LDQ, LDZ, N
206* ..
207* .. Array Arguments ..
208 COMPLEX*16 A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
209 $ z( ldz, * )
210* ..
211*
212* =====================================================================
213*
214* .. Local Scalars ..
215 INTEGER HERE
216* ..
217* .. External Subroutines ..
218 EXTERNAL xerbla, ztgex2
219* ..
220* .. Intrinsic Functions ..
221 INTRINSIC max
222* ..
223* .. Executable Statements ..
224*
225* Decode and test input arguments.
226 info = 0
227 IF( n.LT.0 ) THEN
228 info = -3
229 ELSE IF( lda.LT.max( 1, n ) ) THEN
230 info = -5
231 ELSE IF( ldb.LT.max( 1, n ) ) THEN
232 info = -7
233 ELSE IF( ldq.LT.1 .OR. wantq .AND. ( ldq.LT.max( 1, n ) ) ) THEN
234 info = -9
235 ELSE IF( ldz.LT.1 .OR. wantz .AND. ( ldz.LT.max( 1, n ) ) ) THEN
236 info = -11
237 ELSE IF( ifst.LT.1 .OR. ifst.GT.n ) THEN
238 info = -12
239 ELSE IF( ilst.LT.1 .OR. ilst.GT.n ) THEN
240 info = -13
241 END IF
242 IF( info.NE.0 ) THEN
243 CALL xerbla( 'ZTGEXC', -info )
244 RETURN
245 END IF
246*
247* Quick return if possible
248*
249 IF( n.LE.1 )
250 $ RETURN
251 IF( ifst.EQ.ilst )
252 $ RETURN
253*
254 IF( ifst.LT.ilst ) THEN
255*
256 here = ifst
257*
258 10 CONTINUE
259*
260* Swap with next one below
261*
262 CALL ztgex2( wantq, wantz, n, a, lda, b, ldb, q, ldq, z,
263 $ ldz,
264 $ here, info )
265 IF( info.NE.0 ) THEN
266 ilst = here
267 RETURN
268 END IF
269 here = here + 1
270 IF( here.LT.ilst )
271 $ GO TO 10
272 here = here - 1
273 ELSE
274 here = ifst - 1
275*
276 20 CONTINUE
277*
278* Swap with next one above
279*
280 CALL ztgex2( wantq, wantz, n, a, lda, b, ldb, q, ldq, z,
281 $ ldz,
282 $ here, info )
283 IF( info.NE.0 ) THEN
284 ilst = here
285 RETURN
286 END IF
287 here = here - 1
288 IF( here.GE.ilst )
289 $ GO TO 20
290 here = here + 1
291 END IF
292 ilst = here
293 RETURN
294*
295* End of ZTGEXC
296*
297 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ztgex2(wantq, wantz, n, a, lda, b, ldb, q, ldq, z, ldz, j1, info)
ZTGEX2 swaps adjacent diagonal blocks in an upper (quasi) triangular matrix pair by an unitary equiva...
Definition ztgex2.f:188
subroutine ztgexc(wantq, wantz, n, a, lda, b, ldb, q, ldq, z, ldz, ifst, ilst, info)
ZTGEXC
Definition ztgexc.f:198