3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CTREXC + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ctrexc.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ctrexc.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ctrexc.f">
21 * SUBROUTINE CTREXC( COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER IFST, ILST, INFO, LDQ, LDT, N
27 * .. Array Arguments ..
28 * COMPLEX Q( LDQ, * ), T( LDT, * )
37 *> CTREXC reorders the Schur factorization of a complex matrix
38 *> A = Q*T*Q**H, so that the diagonal element of T with row index IFST
39 *> is moved to row ILST.
41 *> The Schur form T is reordered by a unitary similarity transformation
42 *> Z**H*T*Z, and optionally the matrix Q of Schur vectors is updated by
43 *> postmultplying it with Z.
51 *> COMPQ is CHARACTER*1
52 *> = 'V': update the matrix Q of Schur vectors;
53 *> = 'N': do not update Q.
59 *> The order of the matrix T. N >= 0.
64 *> T is COMPLEX array, dimension (LDT,N)
65 *> On entry, the upper triangular matrix T.
66 *> On exit, the reordered upper triangular matrix.
72 *> The leading dimension of the array T. LDT >= max(1,N).
77 *> Q is COMPLEX array, dimension (LDQ,N)
78 *> On entry, if COMPQ = 'V', the matrix Q of Schur vectors.
79 *> On exit, if COMPQ = 'V', Q has been postmultiplied by the
80 *> unitary transformation matrix Z which reorders T.
81 *> If COMPQ = 'N', Q is not referenced.
87 *> The leading dimension of the array Q. LDQ >= max(1,N).
99 *> Specify the reordering of the diagonal elements of T:
100 *> The element with row index IFST is moved to row ILST by a
101 *> sequence of transpositions between adjacent elements.
102 *> 1 <= IFST <= N; 1 <= ILST <= N.
108 *> = 0: successful exit
109 *> < 0: if INFO = -i, the i-th argument had an illegal value
115 *> \author Univ. of Tennessee
116 *> \author Univ. of California Berkeley
117 *> \author Univ. of Colorado Denver
120 *> \date November 2011
122 *> \ingroup complexOTHERcomputational
124 * =====================================================================
125 SUBROUTINE CTREXC( COMPQ, N, T, LDT, Q, LDQ, IFST, ILST, INFO )
127 * -- LAPACK computational routine (version 3.4.0) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
132 * .. Scalar Arguments ..
134 INTEGER IFST, ILST, INFO, LDQ, LDT, N
136 * .. Array Arguments ..
137 COMPLEX Q( LDQ, * ), T( LDT, * )
140 * =====================================================================
142 * .. Local Scalars ..
144 INTEGER K, M1, M2, M3
146 COMPLEX SN, T11, T22, TEMP
148 * .. External Functions ..
152 * .. External Subroutines ..
153 EXTERNAL CLARTG, CROT, XERBLA
155 * .. Intrinsic Functions ..
158 * .. Executable Statements ..
160 * Decode and test the input parameters.
163 WANTQ = LSAME( COMPQ, 'V' )
164 IF( .NOT.LSAME( COMPQ, 'N' ) .AND. .NOT.WANTQ ) THEN
166 ELSE IF( N.LT.0 ) THEN
168 ELSE IF( LDT.LT.MAX( 1, N ) ) THEN
170 ELSE IF( LDQ.LT.1 .OR. ( WANTQ .AND. LDQ.LT.MAX( 1, N ) ) ) THEN
172 ELSE IF( IFST.LT.1 .OR. IFST.GT.N ) THEN
174 ELSE IF( ILST.LT.1 .OR. ILST.GT.N ) THEN
178 CALL XERBLA( 'CTREXC', -INFO )
182 * Quick return if possible
184 IF( N.EQ.1 .OR. IFST.EQ.ILST )
187 IF( IFST.LT.ILST ) THEN
189 * Move the IFST-th diagonal element forward down the diagonal.
196 * Move the IFST-th diagonal element backward up the diagonal.
203 DO 10 K = IFST + M1, ILST + M2, M3
205 * Interchange the k-th and (k+1)-th diagonal elements.
210 * Determine the transformation to perform the interchange.
212 CALL CLARTG( T( K, K+1 ), T22-T11, CS, SN, TEMP )
214 * Apply transformation to the matrix T.
217 $ CALL CROT( N-K-1, T( K, K+2 ), LDT, T( K+1, K+2 ), LDT, CS,
219 CALL CROT( K-1, T( 1, K ), 1, T( 1, K+1 ), 1, CS, CONJG( SN ) )
226 * Accumulate transformation in the matrix Q.
228 CALL CROT( N, Q( 1, K ), 1, Q( 1, K+1 ), 1, CS,