ctgsen


NAME

ctgsen - reorder the generalized Schur decomposition of a complex matrix pair (A, B) (in terms of an unitary equivalence trans- formation Q' * (A, B) * Z), so that a selected cluster of eigenvalues appears in the leading diagonal blocks of the pair (A,B)


SYNOPSIS

  SUBROUTINE CTGSEN( IJOB, WANTQ, WANTZ, SELECT, N, A, LDA, B, LDB, 
 *      ALPHA, BETA, Q, LDQ, Z, LDZ, M, PL, PR, DIF, WORK, LWORK, IWORK, 
 *      LIWORK, INFO)
  COMPLEX A(LDA,*), B(LDB,*), ALPHA(*), BETA(*), Q(LDQ,*), Z(LDZ,*), WORK(*)
  INTEGER IJOB, N, LDA, LDB, LDQ, LDZ, M, LWORK, LIWORK, INFO
  INTEGER IWORK(*)
  LOGICAL WANTQ, WANTZ
  LOGICAL SELECT(*)
  REAL PL, PR
  REAL DIF(*)
 
  SUBROUTINE CTGSEN_64( IJOB, WANTQ, WANTZ, SELECT, N, A, LDA, B, LDB, 
 *      ALPHA, BETA, Q, LDQ, Z, LDZ, M, PL, PR, DIF, WORK, LWORK, IWORK, 
 *      LIWORK, INFO)
  COMPLEX A(LDA,*), B(LDB,*), ALPHA(*), BETA(*), Q(LDQ,*), Z(LDZ,*), WORK(*)
  INTEGER*8 IJOB, N, LDA, LDB, LDQ, LDZ, M, LWORK, LIWORK, INFO
  INTEGER*8 IWORK(*)
  LOGICAL*8 WANTQ, WANTZ
  LOGICAL*8 SELECT(*)
  REAL PL, PR
  REAL DIF(*)
 

F95 INTERFACE

  SUBROUTINE TGSEN( IJOB, WANTQ, WANTZ, SELECT, [N], A, [LDA], B, [LDB], 
 *       ALPHA, BETA, Q, [LDQ], Z, [LDZ], M, PL, PR, DIF, [WORK], [LWORK], 
 *       [IWORK], [LIWORK], [INFO])
  COMPLEX, DIMENSION(:) :: ALPHA, BETA, WORK
  COMPLEX, DIMENSION(:,:) :: A, B, Q, Z
  INTEGER :: IJOB, N, LDA, LDB, LDQ, LDZ, M, LWORK, LIWORK, INFO
  INTEGER, DIMENSION(:) :: IWORK
  LOGICAL :: WANTQ, WANTZ
  LOGICAL, DIMENSION(:) :: SELECT
  REAL :: PL, PR
  REAL, DIMENSION(:) :: DIF
 
  SUBROUTINE TGSEN_64( IJOB, WANTQ, WANTZ, SELECT, [N], A, [LDA], B, 
 *       [LDB], ALPHA, BETA, Q, [LDQ], Z, [LDZ], M, PL, PR, DIF, [WORK], 
 *       [LWORK], [IWORK], [LIWORK], [INFO])
  COMPLEX, DIMENSION(:) :: ALPHA, BETA, WORK
  COMPLEX, DIMENSION(:,:) :: A, B, Q, Z
  INTEGER(8) :: IJOB, N, LDA, LDB, LDQ, LDZ, M, LWORK, LIWORK, INFO
  INTEGER(8), DIMENSION(:) :: IWORK
  LOGICAL(8) :: WANTQ, WANTZ
  LOGICAL(8), DIMENSION(:) :: SELECT
  REAL :: PL, PR
  REAL, DIMENSION(:) :: DIF
 

C INTERFACE

#include <sunperf.h>

void ctgsen(int ijob, logical wantq, logical wantz, logical *select, int n, complex *a, int lda, complex *b, int ldb, complex *alpha, complex *beta, complex *q, int ldq, complex *z, int ldz, int *m, float *pl, float *pr, float *dif, int *info);

void ctgsen_64(long ijob, logical wantq, logical wantz, logical *select, long n, complex *a, long lda, complex *b, long ldb, complex *alpha, complex *beta, complex *q, long ldq, complex *z, long ldz, long *m, float *pl, float *pr, float *dif, long *info);


PURPOSE

ctgsen reorders the generalized Schur decomposition of a complex matrix pair (A, B) (in terms of an unitary equivalence trans- formation Q' * (A, B) * Z), so that a selected cluster of eigenvalues appears in the leading diagonal blocks of the pair (A,B). The leading columns of Q and Z form unitary bases of the corresponding left and right eigenspaces (deflating subspaces). (A, B) must be in generalized Schur canonical form, that is, A and B are both upper triangular.

CTGSEN also computes the generalized eigenvalues

         w(j)= ALPHA(j) / BETA(j)

of the reordered matrix pair (A, B).

Optionally, the routine computes estimates of reciprocal condition numbers for eigenvalues and eigenspaces. These are Difu[(A11,B11), (A22,B22)] and Difl[(A11,B11), (A22,B22)], i.e. the separation(s) between the matrix pairs (A11, B11) and (A22,B22) that correspond to the selected cluster and the eigenvalues outside the cluster, resp., and norms of ``projections'' onto left and right eigenspaces w.r.t. the selected cluster in the (1,1)-block.


ARGUMENTS

* IJOB (input)
Specifies whether condition numbers are required for the cluster of eigenvalues (PL and PR) or the deflating subspaces (Difu and Difl):

* 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.

* SELECT (input)
SELECT specifies the eigenvalues in the selected cluster. To select an eigenvalue w(j), SELECT(j) must be set to .TRUE..

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

* A (input/output)
On entry, the upper triangular matrix A, in generalized Schur canonical form. On exit, A is overwritten by the reordered 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 generalized Schur canonical form. On exit, B is overwritten by the reordered matrix B.

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

* ALPHA (output)
The diagonal elements of A and B, respectively, when the pair (A,B) has been reduced to generalized Schur form. ALPHA(i)/BETA(i) i=1,...,N are the generalized eigenvalues.

* BETA (output)
See the description of ALPHA.

* Q (input/output)
On entry, if WANTQ = .TRUE., Q is an N-by-N matrix. On exit, Q has been postmultiplied by the left unitary transformation matrix which reorder (A, B); The leading M columns of Q form orthonormal bases for the specified pair of left eigenspaces (deflating subspaces). 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., Z is an N-by-N matrix. On exit, Z has been postmultiplied by the left unitary transformation matrix which reorder (A, B); The leading M columns of Z form orthonormal bases for the specified pair of left eigenspaces (deflating subspaces). If WANTZ = .FALSE., Z is not referenced.

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

* M (output)
The dimension of the specified pair of left and right eigenspaces, (deflating subspaces) 0 <= M <= N.

* PL (output)
IF IJOB = 1, 4, or 5, PL, PR are lower bounds on the reciprocal of the norm of ``projections'' onto left and right eigenspace with respect to the selected cluster.

0 < PL, PR <= 1. If M = 0 or M = N, PL = PR = 1. If IJOB = 0, 2, or 3 PL, PR are not referenced.

* PR (output)
See the description of PL.

* DIF (output)
If IJOB >= 2, DIF(1:2) store the estimates of Difu and Difl.

If IJOB = 2 or 4, DIF(1:2) are F-norm-based upper bounds on

Difu and Difl. If IJOB = 3 or 5, DIF(1:2) are 1-norm-based estimates of Difu and Difl, computed using reversed communication with CLACON. If M = 0 or N, DIF(1:2) = F-norm([A, B]). If IJOB = 0 or 1, DIF is not referenced.

* WORK (workspace)
If IJOB = 0, WORK is not referenced. Otherwise, on exit, if INFO = 0, WORK(1) returns the optimal LWORK.

* LWORK (input)
The dimension of the array WORK. LWORK >= 1 If IJOB = 1, 2 or 4, LWORK >= 2*M*(N-M) If IJOB = 3 or 5, LWORK >= 4*M*(N-M)

If LWORK = -1, then a workspace query is assumed; the routine only calculates the optimal size of the WORK array, returns this value as the first entry of the WORK array, and no error message related to LWORK is issued by XERBLA.

* IWORK (workspace)
If IJOB = 0, IWORK is not referenced. Otherwise, on exit, if INFO = 0, IWORK(1) returns the optimal LIWORK.

* LIWORK (input)
The dimension of the array IWORK. LIWORK >= 1. If IJOB = 1, 2 or 4, LIWORK >= N+2; If IJOB = 3 or 5, LIWORK >= MAX(N+2, 2*M*(N-M));

If LIWORK = -1, then a workspace query is assumed; the routine only calculates the optimal size of the IWORK array, returns this value as the first entry of the IWORK array, and no error message related to LIWORK is issued by XERBLA.

* INFO (output)