LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ ztrexc()

subroutine ztrexc ( character compq,
integer n,
complex*16, dimension( ldt, * ) t,
integer ldt,
complex*16, dimension( ldq, * ) q,
integer ldq,
integer ifst,
integer ilst,
integer info )

ZTREXC

Download ZTREXC + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> ZTREXC reorders the Schur factorization of a complex matrix
!> A = Q*T*Q**H, so that the diagonal element of T with row index IFST
!> is moved to row ILST.
!>
!> The Schur form T is reordered by a unitary similarity transformation
!> Z**H*T*Z, and optionally the matrix Q of Schur vectors is updated by
!> postmultiplying it with Z.
!> 
Parameters
[in]COMPQ
!>          COMPQ is CHARACTER*1
!>          = 'V':  update the matrix Q of Schur vectors;
!>          = 'N':  do not update Q.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix T. N >= 0.
!>          If N == 0 arguments ILST and IFST may be any value.
!> 
[in,out]T
!>          T is COMPLEX*16 array, dimension (LDT,N)
!>          On entry, the upper triangular matrix T.
!>          On exit, the reordered upper triangular matrix.
!> 
[in]LDT
!>          LDT is INTEGER
!>          The leading dimension of the array T. LDT >= max(1,N).
!> 
[in,out]Q
!>          Q is COMPLEX*16 array, dimension (LDQ,N)
!>          On entry, if COMPQ = 'V', the matrix Q of Schur vectors.
!>          On exit, if COMPQ = 'V', Q has been postmultiplied by the
!>          unitary transformation matrix Z which reorders T.
!>          If COMPQ = 'N', Q is not referenced.
!> 
[in]LDQ
!>          LDQ is INTEGER
!>          The leading dimension of the array Q.  LDQ >= 1, and if
!>          COMPQ = 'V', LDQ >= max(1,N).
!> 
[in]IFST
!>          IFST is INTEGER
!> 
[in]ILST
!>          ILST is INTEGER
!>
!>          Specify the reordering of the diagonal elements of T:
!>          The element with row index IFST is moved to row ILST by a
!>          sequence of transpositions between adjacent elements.
!>          1 <= IFST <= N; 1 <= ILST <= N.
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -i, the i-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 123 of file ztrexc.f.

124*
125* -- LAPACK computational routine --
126* -- LAPACK is a software package provided by Univ. of Tennessee, --
127* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
128*
129* .. Scalar Arguments ..
130 CHARACTER COMPQ
131 INTEGER IFST, ILST, INFO, LDQ, LDT, N
132* ..
133* .. Array Arguments ..
134 COMPLEX*16 Q( LDQ, * ), T( LDT, * )
135* ..
136*
137* =====================================================================
138*
139* .. Local Scalars ..
140 LOGICAL WANTQ
141 INTEGER K, M1, M2, M3
142 DOUBLE PRECISION CS
143 COMPLEX*16 SN, T11, T22, TEMP
144* ..
145* .. External Functions ..
146 LOGICAL LSAME
147 EXTERNAL lsame
148* ..
149* .. External Subroutines ..
150 EXTERNAL xerbla, zlartg, zrot
151* ..
152* .. Intrinsic Functions ..
153 INTRINSIC dconjg, max
154* ..
155* .. Executable Statements ..
156*
157* Decode and test the input parameters.
158*
159 info = 0
160 wantq = lsame( compq, 'V' )
161 IF( .NOT.lsame( compq, 'N' ) .AND. .NOT.wantq ) THEN
162 info = -1
163 ELSE IF( n.LT.0 ) THEN
164 info = -2
165 ELSE IF( ldt.LT.max( 1, n ) ) THEN
166 info = -4
167 ELSE IF( ldq.LT.1 .OR. ( wantq .AND. ldq.LT.max( 1, n ) ) ) THEN
168 info = -6
169 ELSE IF(( ifst.LT.1 .OR. ifst.GT.n ).AND.( n.GT.0 )) THEN
170 info = -7
171 ELSE IF(( ilst.LT.1 .OR. ilst.GT.n ).AND.( n.GT.0 )) THEN
172 info = -8
173 END IF
174 IF( info.NE.0 ) THEN
175 CALL xerbla( 'ZTREXC', -info )
176 RETURN
177 END IF
178*
179* Quick return if possible
180*
181 IF( n.LE.1 .OR. ifst.EQ.ilst )
182 $ RETURN
183*
184 IF( ifst.LT.ilst ) THEN
185*
186* Move the IFST-th diagonal element forward down the diagonal.
187*
188 m1 = 0
189 m2 = -1
190 m3 = 1
191 ELSE
192*
193* Move the IFST-th diagonal element backward up the diagonal.
194*
195 m1 = -1
196 m2 = 0
197 m3 = -1
198 END IF
199*
200 DO 10 k = ifst + m1, ilst + m2, m3
201*
202* Interchange the k-th and (k+1)-th diagonal elements.
203*
204 t11 = t( k, k )
205 t22 = t( k+1, k+1 )
206*
207* Determine the transformation to perform the interchange.
208*
209 CALL zlartg( t( k, k+1 ), t22-t11, cs, sn, temp )
210*
211* Apply transformation to the matrix T.
212*
213 IF( k+2.LE.n )
214 $ CALL zrot( n-k-1, t( k, k+2 ), ldt, t( k+1, k+2 ), ldt,
215 $ cs,
216 $ sn )
217 CALL zrot( k-1, t( 1, k ), 1, t( 1, k+1 ), 1, cs,
218 $ dconjg( sn ) )
219*
220 t( k, k ) = t22
221 t( k+1, k+1 ) = t11
222*
223 IF( wantq ) THEN
224*
225* Accumulate transformation in the matrix Q.
226*
227 CALL zrot( n, q( 1, k ), 1, q( 1, k+1 ), 1, cs,
228 $ dconjg( sn ) )
229 END IF
230*
231 10 CONTINUE
232*
233 RETURN
234*
235* End of ZTREXC
236*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine zlartg(f, g, c, s, r)
ZLARTG generates a plane rotation with real cosine and complex sine.
Definition zlartg.f90:116
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine zrot(n, cx, incx, cy, incy, c, s)
ZROT applies a plane rotation with real cosine and complex sine to a pair of complex vectors.
Definition zrot.f:101
Here is the call graph for this function:
Here is the caller graph for this function: