ctgexc


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

* WANTQ (input)
.TRUE. : update the left transformation matrix Q;

.FALSE.: do not update Q.

* WANTZ (input)
.TRUE. : update the right transformation matrix Z;

.FALSE.: do not update Z.

* N (input)
The order of the matrices A and B. N >= 0.

* A (input/output)
On entry, the upper triangular matrix A in the pair (A, B). On exit, the updated matrix A.

* LDA (input)
The leading dimension of the array A. LDA >= max(1,N).

* B (input/output)
On entry, the upper triangular matrix B in the pair (A, B). On exit, the updated matrix B.

* LDB (input)
The leading dimension of the array B. LDB >= max(1,N).

* Q (input/output)
On entry, if WANTQ = .TRUE., the unitary matrix Q. On exit, the updated matrix Q. If WANTQ = .FALSE., Q is not referenced.

* LDQ (input)
The leading dimension of the array Q. LDQ >= 1; If WANTQ = .TRUE., LDQ >= N.

* Z (input/output)
On entry, if WANTZ = .TRUE., the unitary matrix Z. On exit, the updated matrix Z. If WANTZ = .FALSE., Z is not referenced.

* LDZ (input)
The leading dimension of the array Z. LDZ >= 1; If WANTZ = .TRUE., LDZ >= N.

* IFST (input/output)
Specify the reordering of the diagonal blocks of (A, B). The block with row index IFST is moved to row ILST, by a sequence of swapping between adjacent blocks.

* ILST (input/output)
See the description of IFST.

* INFO (output)