3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZTGEXC + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztgexc.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztgexc.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgexc.f">
21 * SUBROUTINE ZTGEXC( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
22 * LDZ, IFST, ILST, INFO )
24 * .. Scalar Arguments ..
25 * LOGICAL WANTQ, WANTZ
26 * INTEGER IFST, ILST, INFO, LDA, LDB, LDQ, LDZ, N
28 * .. Array Arguments ..
29 * COMPLEX*16 A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
39 *> ZTGEXC reorders the generalized Schur decomposition of a complex
40 *> matrix pair (A,B), using an unitary equivalence transformation
41 *> (A, B) := Q * (A, B) * Z**H, so that the diagonal block of (A, B) with
42 *> row index IFST is moved to row ILST.
44 *> (A, B) must be in generalized Schur canonical form, that is, A and
45 *> B are both upper triangular.
47 *> Optionally, the matrices Q and Z of generalized Schur vectors are
50 *> Q(in) * A(in) * Z(in)**H = Q(out) * A(out) * Z(out)**H
51 *> Q(in) * B(in) * Z(in)**H = Q(out) * B(out) * Z(out)**H
60 *> .TRUE. : update the left transformation matrix Q;
61 *> .FALSE.: do not update Q.
67 *> .TRUE. : update the right transformation matrix Z;
68 *> .FALSE.: do not update Z.
74 *> The order of the matrices A and B. N >= 0.
79 *> A is COMPLEX*16 array, dimension (LDA,N)
80 *> On entry, the upper triangular matrix A in the pair (A, B).
81 *> On exit, the updated matrix A.
87 *> The leading dimension of the array A. LDA >= max(1,N).
92 *> B is COMPLEX*16 array, dimension (LDB,N)
93 *> On entry, the upper triangular matrix B in the pair (A, B).
94 *> On exit, the updated matrix B.
100 *> The leading dimension of the array B. LDB >= max(1,N).
105 *> Q is COMPLEX*16 array, dimension (LDZ,N)
106 *> On entry, if WANTQ = .TRUE., the unitary matrix Q.
107 *> On exit, the updated matrix Q.
108 *> If WANTQ = .FALSE., Q is not referenced.
114 *> The leading dimension of the array Q. LDQ >= 1;
115 *> If WANTQ = .TRUE., LDQ >= N.
120 *> Z is COMPLEX*16 array, dimension (LDZ,N)
121 *> On entry, if WANTZ = .TRUE., the unitary matrix Z.
122 *> On exit, the updated matrix Z.
123 *> If WANTZ = .FALSE., Z is not referenced.
129 *> The leading dimension of the array Z. LDZ >= 1;
130 *> If WANTZ = .TRUE., LDZ >= N.
138 *> \param[in,out] ILST
141 *> Specify the reordering of the diagonal blocks of (A, B).
142 *> The block with row index IFST is moved to row ILST, by a
143 *> sequence of swapping between adjacent blocks.
149 *> =0: Successful exit.
150 *> <0: if INFO = -i, the i-th argument had an illegal value.
151 *> =1: The transformed matrix pair (A, B) would be too far
152 *> from generalized Schur form; the problem is ill-
153 *> conditioned. (A, B) may have been partially reordered,
154 *> and ILST points to the first row of the current
155 *> position of the block being moved.
161 *> \author Univ. of Tennessee
162 *> \author Univ. of California Berkeley
163 *> \author Univ. of Colorado Denver
166 *> \date November 2011
168 *> \ingroup complex16GEcomputational
170 *> \par Contributors:
173 *> Bo Kagstrom and Peter Poromaa, Department of Computing Science,
174 *> Umea University, S-901 87 Umea, Sweden.
179 *> [1] B. Kagstrom; A Direct Method for Reordering Eigenvalues in the
180 *> Generalized Real Schur Form of a Regular Matrix Pair (A, B), in
181 *> M.S. Moonen et al (eds), Linear Algebra for Large Scale and
182 *> Real-Time Applications, Kluwer Academic Publ. 1993, pp 195-218.
184 *> [2] B. Kagstrom and P. Poromaa; Computing Eigenspaces with Specified
185 *> Eigenvalues of a Regular Matrix Pair (A, B) and Condition
186 *> Estimation: Theory, Algorithms and Software, Report
187 *> UMINF - 94.04, Department of Computing Science, Umea University,
188 *> S-901 87 Umea, Sweden, 1994. Also as LAPACK Working Note 87.
189 *> To appear in Numerical Algorithms, 1996.
191 *> [3] B. Kagstrom and P. Poromaa, LAPACK-Style Algorithms and Software
192 *> for Solving the Generalized Sylvester Equation and Estimating the
193 *> Separation between Regular Matrix Pairs, Report UMINF - 93.23,
194 *> Department of Computing Science, Umea University, S-901 87 Umea,
195 *> Sweden, December 1993, Revised April 1994, Also as LAPACK working
196 *> Note 75. To appear in ACM Trans. on Math. Software, Vol 22, No 1,
199 * =====================================================================
200 SUBROUTINE ZTGEXC( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z,
201 $ LDZ, IFST, ILST, INFO )
203 * -- LAPACK computational routine (version 3.4.0) --
204 * -- LAPACK is a software package provided by Univ. of Tennessee, --
205 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
208 * .. Scalar Arguments ..
210 INTEGER IFST, ILST, INFO, LDA, LDB, LDQ, LDZ, N
212 * .. Array Arguments ..
213 COMPLEX*16 A( LDA, * ), B( LDB, * ), Q( LDQ, * ),
217 * =====================================================================
219 * .. Local Scalars ..
222 * .. External Subroutines ..
223 EXTERNAL XERBLA, ZTGEX2
225 * .. Intrinsic Functions ..
228 * .. Executable Statements ..
230 * Decode and test input arguments.
234 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
236 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
238 ELSE IF( LDQ.LT.1 .OR. WANTQ .AND. ( LDQ.LT.MAX( 1, N ) ) ) THEN
240 ELSE IF( LDZ.LT.1 .OR. WANTZ .AND. ( LDZ.LT.MAX( 1, N ) ) ) THEN
242 ELSE IF( IFST.LT.1 .OR. IFST.GT.N ) THEN
244 ELSE IF( ILST.LT.1 .OR. ILST.GT.N ) THEN
248 CALL XERBLA( 'ZTGEXC', -INFO )
252 * Quick return if possible
259 IF( IFST.LT.ILST ) THEN
265 * Swap with next one below
267 CALL ZTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z, LDZ,
282 * Swap with next one above
284 CALL ZTGEX2( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z, LDZ,