ztrsen


NAME

ztrsen - reorder the Schur factorization of a complex matrix A = Q*T*Q**H, so that a selected cluster of eigenvalues appears in the leading positions on the diagonal of the upper triangular matrix T, and the leading columns of Q form an orthonormal basis of the corresponding right invariant subspace


SYNOPSIS

  SUBROUTINE ZTRSEN( JOB, COMPQ, SELECT, N, T, LDT, Q, LDQ, W, M, S, 
 *      SEP, WORK, LWORK, INFO)
  CHARACTER * 1 JOB, COMPQ
  DOUBLE COMPLEX T(LDT,*), Q(LDQ,*), W(*), WORK(*)
  INTEGER N, LDT, LDQ, M, LWORK, INFO
  LOGICAL SELECT(*)
  DOUBLE PRECISION S, SEP
 
  SUBROUTINE ZTRSEN_64( JOB, COMPQ, SELECT, N, T, LDT, Q, LDQ, W, M, 
 *      S, SEP, WORK, LWORK, INFO)
  CHARACTER * 1 JOB, COMPQ
  DOUBLE COMPLEX T(LDT,*), Q(LDQ,*), W(*), WORK(*)
  INTEGER*8 N, LDT, LDQ, M, LWORK, INFO
  LOGICAL*8 SELECT(*)
  DOUBLE PRECISION S, SEP
 

F95 INTERFACE

  SUBROUTINE TRSEN( JOB, COMPQ, SELECT, [N], T, [LDT], Q, [LDQ], W, M, 
 *       S, SEP, [WORK], [LWORK], [INFO])
  CHARACTER(LEN=1) :: JOB, COMPQ
  COMPLEX(8), DIMENSION(:) :: W, WORK
  COMPLEX(8), DIMENSION(:,:) :: T, Q
  INTEGER :: N, LDT, LDQ, M, LWORK, INFO
  LOGICAL, DIMENSION(:) :: SELECT
  REAL(8) :: S, SEP
 
  SUBROUTINE TRSEN_64( JOB, COMPQ, SELECT, [N], T, [LDT], Q, [LDQ], W, 
 *       M, S, SEP, [WORK], [LWORK], [INFO])
  CHARACTER(LEN=1) :: JOB, COMPQ
  COMPLEX(8), DIMENSION(:) :: W, WORK
  COMPLEX(8), DIMENSION(:,:) :: T, Q
  INTEGER(8) :: N, LDT, LDQ, M, LWORK, INFO
  LOGICAL(8), DIMENSION(:) :: SELECT
  REAL(8) :: S, SEP
 

C INTERFACE

#include <sunperf.h>

void ztrsen(char job, char compq, logical *select, int n, doublecomplex *t, int ldt, doublecomplex *q, int ldq, doublecomplex *w, int *m, double *s, double *sep, int *info);

void ztrsen_64(char job, char compq, logical *select, long n, doublecomplex *t, long ldt, doublecomplex *q, long ldq, doublecomplex *w, long *m, double *s, double *sep, long *info);


PURPOSE

ztrsen reorders the Schur factorization of a complex matrix A = Q*T*Q**H, so that a selected cluster of eigenvalues appears in the leading positions on the diagonal of the upper triangular matrix T, and the leading columns of Q form an orthonormal basis of the corresponding right invariant subspace.

Optionally the routine computes the reciprocal condition numbers of the cluster of eigenvalues and/or the invariant subspace.


ARGUMENTS

* JOB (input)
Specifies whether condition numbers are required for the cluster of eigenvalues (S) or the invariant subspace (SEP):

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

* N (input)
The order of the matrix T. N >= 0.

* T (input/output)
On entry, the upper triangular matrix T. On exit, T is overwritten by the reordered matrix T, with the selected eigenvalues as the leading diagonal elements.

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

* Q (input)
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 which reorders T; the leading M columns of Q form an orthonormal basis for the specified invariant subspace. If COMPQ = 'N', Q is not referenced.

* LDQ (input)
The leading dimension of the array Q. LDQ >= 1; and if COMPQ = 'V', LDQ >= N.

* W (output)
The reordered eigenvalues of T, in the same order as they appear on the diagonal of T.

* M (output)
The dimension of the specified invariant subspace. 0 <= M <= N.

* S (output)
If JOB = 'E' or 'B', S is a lower bound on the reciprocal condition number for the selected cluster of eigenvalues. S cannot underestimate the true reciprocal condition number by more than a factor of sqrt(N). If M = 0 or N, S = 1. If JOB = 'N' or 'V', S is not referenced.

* SEP (output)
If JOB = 'V' or 'B', SEP is the estimated reciprocal condition number of the specified invariant subspace. If M = 0 or N, SEP = norm(T). If JOB = 'N' or 'E', SEP is not referenced.

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

* LWORK (input)
The dimension of the array WORK. If JOB = 'N', LWORK >= 1; if JOB = 'E', LWORK = M*(N-M); if JOB = 'V' or 'B', LWORK >= 2*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.

* INFO (output)