NAME

ctgexc - reorder the generalized Schur decomposition of a complex matrix pair (A,B), using an unitary equivalence transformation (A, B) := Q * (A, B) * Z', so that the diagonal block of (A, B) with row index IFST is moved to row ILST


SYNOPSIS

  SUBROUTINE CTGEXC( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z, LDZ, 
 *      IFST, ILST, INFO)
  COMPLEX A(LDA,*), B(LDB,*), Q(LDQ,*), Z(LDZ,*)
  INTEGER N, LDA, LDB, LDQ, LDZ, IFST, ILST, INFO
  LOGICAL WANTQ, WANTZ
  SUBROUTINE CTGEXC_64( WANTQ, WANTZ, N, A, LDA, B, LDB, Q, LDQ, Z, 
 *      LDZ, IFST, ILST, INFO)
  COMPLEX A(LDA,*), B(LDB,*), Q(LDQ,*), Z(LDZ,*)
  INTEGER*8 N, LDA, LDB, LDQ, LDZ, IFST, ILST, INFO
  LOGICAL*8 WANTQ, WANTZ

F95 INTERFACE

  SUBROUTINE TGEXC( WANTQ, WANTZ, [N], A, [LDA], B, [LDB], Q, [LDQ], 
 *       Z, [LDZ], IFST, ILST, [INFO])
  COMPLEX, DIMENSION(:,:) :: A, B, Q, Z
  INTEGER :: N, LDA, LDB, LDQ, LDZ, IFST, ILST, INFO
  LOGICAL :: WANTQ, WANTZ
  SUBROUTINE TGEXC_64( WANTQ, WANTZ, [N], A, [LDA], B, [LDB], Q, [LDQ], 
 *       Z, [LDZ], IFST, ILST, [INFO])
  COMPLEX, DIMENSION(:,:) :: A, B, Q, Z
  INTEGER(8) :: N, LDA, LDB, LDQ, LDZ, IFST, ILST, INFO
  LOGICAL(8) :: WANTQ, WANTZ

C INTERFACE

#include <sunperf.h>

void ctgexc(logical wantq, logical wantz, int n, complex *a, int lda, complex *b, int ldb, complex *q, int ldq, complex *z, int ldz, int *ifst, int *ilst, int *info);

void ctgexc_64(logical wantq, logical wantz, long n, complex *a, long lda, complex *b, long ldb, complex *q, long ldq, complex *z, long ldz, long *ifst, long *ilst, long *info);


PURPOSE

ctgexc reorders the generalized Schur decomposition of a complex matrix pair (A,B), using an unitary equivalence transformation (A, B) := Q * (A, B) * Z', so that the diagonal block of (A, B) with row index IFST is moved to row ILST.

(A, B) must be in generalized Schur canonical form, that is, A and B are both upper triangular.

Optionally, the matrices Q and Z of generalized Schur vectors are updated.

       Q(in) * A(in) * Z(in)' = Q(out) * A(out) * Z(out)'
       Q(in) * B(in) * Z(in)' = Q(out) * B(out) * Z(out)'


ARGUMENTS


FURTHER DETAILS

Based on contributions by

   Bo Kagstrom and Peter Poromaa, Department of Computing Science,
   Umea University, S-901 87 Umea, Sweden.

[1] B. Kagstrom; A Direct Method for Reordering Eigenvalues in the Generalized Real Schur Form of a Regular Matrix Pair (A, B), in M.S. Moonen et al (eds), Linear Algebra for Large Scale and Real-Time Applications, Kluwer Academic Publ. 1993, pp 195-218.

[2] B. Kagstrom and P. Poromaa; Computing Eigenspaces with Specified Eigenvalues of a Regular Matrix Pair (A, B) and Condition Estimation: Theory, Algorithms and Software, Report

    UMINF - 94.04, Department of Computing Science, Umea University,
    S-901 87 Umea, Sweden, 1994. Also as LAPACK Working Note 87.
    To appear in Numerical Algorithms, 1996.

[3] B. Kagstrom and P. Poromaa, LAPACK-Style Algorithms and Software for Solving the Generalized Sylvester Equation and Estimating the Separation between Regular Matrix Pairs, Report UMINF - 93.23, Department of Computing Science, Umea University, S-901 87 Umea, Sweden, December 1993, Revised April 1994, Also as LAPACK working Note 75. To appear in ACM Trans. on Math. Software, Vol 22, No 1, 1996.