dtrsen


NAME

dtrsen - reorder the real Schur factorization of a real matrix A = Q*T*Q**T, so that a selected cluster of eigenvalues appears in the leading diagonal blocks of the upper quasi-triangular matrix T,


SYNOPSIS

  SUBROUTINE DTRSEN( JOB, COMPQ, SELECT, N, T, LDT, Q, LDQ, WR, WI, M, 
 *      S, SEP, WORK, LWORK, IWORK, LIWORK, INFO)
  CHARACTER * 1 JOB, COMPQ
  INTEGER N, LDT, LDQ, M, LWORK, LIWORK, INFO
  INTEGER IWORK(*)
  LOGICAL SELECT(*)
  DOUBLE PRECISION S, SEP
  DOUBLE PRECISION T(LDT,*), Q(LDQ,*), WR(*), WI(*), WORK(*)
 
  SUBROUTINE DTRSEN_64( JOB, COMPQ, SELECT, N, T, LDT, Q, LDQ, WR, WI, 
 *      M, S, SEP, WORK, LWORK, IWORK, LIWORK, INFO)
  CHARACTER * 1 JOB, COMPQ
  INTEGER*8 N, LDT, LDQ, M, LWORK, LIWORK, INFO
  INTEGER*8 IWORK(*)
  LOGICAL*8 SELECT(*)
  DOUBLE PRECISION S, SEP
  DOUBLE PRECISION T(LDT,*), Q(LDQ,*), WR(*), WI(*), WORK(*)
 

F95 INTERFACE

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

C INTERFACE

#include <sunperf.h>

void dtrsen(char job, char compq, logical *select, int n, double *t, int ldt, double *q, int ldq, double *wr, double *wi, int *m, double *s, double *sep, int *info);

void dtrsen_64(char job, char compq, logical *select, long n, double *t, long ldt, double *q, long ldq, double *wr, double *wi, long *m, double *s, double *sep, long *info);


PURPOSE

dtrsen reorders the real Schur factorization of a real matrix A = Q*T*Q**T, so that a selected cluster of eigenvalues appears in the leading diagonal blocks of the upper quasi-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.

T must be in Schur canonical form (as returned by SHSEQR), that is, block upper triangular with 1-by-1 and 2-by-2 diagonal blocks; each 2-by-2 diagonal block has its diagonal elemnts equal and its off-diagonal elements of opposite sign.


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 a real eigenvalue w(j), SELECT(j) must be set to .TRUE.. To select a complex conjugate pair of eigenvalues w(j) and w(j+1), corresponding to a 2-by-2 diagonal block, either SELECT(j) or SELECT(j+1) or both must be set to .TRUE.; a complex conjugate pair of eigenvalues must be either both included in the cluster or both excluded.

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

* T (input/output)
On entry, the upper quasi-triangular matrix T, in Schur canonical form. On exit, T is overwritten by the reordered matrix T, again in Schur canonical form, with the selected eigenvalues in the leading diagonal blocks.

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

* WR (output)
The real and imaginary parts, respectively, of the reordered eigenvalues of T. The eigenvalues are stored in the same order as on the diagonal of T, with WR(i) = T(i,i) and, if T(i:i+1,i:i+1) is a 2-by-2 diagonal block, WI(i) > 0 and WI(i+1) = -WI(i). Note that if a complex eigenvalue is sufficiently ill-conditioned, then its value may differ significantly from its value before reordering.

* WI (output)
See the description of WR.

* 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)
On exit, if INFO = 0, WORK(1) returns the optimal LWORK.

* LWORK (input)
The dimension of the array WORK. If JOB = 'N', LWORK >= max(1,N); 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.

* IWORK (workspace)
If JOB = 'N' or 'E', IWORK is not referenced.

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