NAME

dtrsna - estimate reciprocal condition numbers for specified eigenvalues and/or right eigenvectors of a real upper quasi-triangular matrix T (or of any matrix Q*T*Q**T with Q orthogonal)


SYNOPSIS

  SUBROUTINE DTRSNA( JOB, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR, 
 *      LDVR, S, SEP, MM, M, WORK, LDWORK, WORK1, INFO)
  CHARACTER * 1 JOB, HOWMNY
  INTEGER N, LDT, LDVL, LDVR, MM, M, LDWORK, INFO
  INTEGER WORK1(*)
  LOGICAL SELECT(*)
  DOUBLE PRECISION T(LDT,*), VL(LDVL,*), VR(LDVR,*), S(*), SEP(*), WORK(LDWORK,*)
  SUBROUTINE DTRSNA_64( JOB, HOWMNY, SELECT, N, T, LDT, VL, LDVL, VR, 
 *      LDVR, S, SEP, MM, M, WORK, LDWORK, WORK1, INFO)
  CHARACTER * 1 JOB, HOWMNY
  INTEGER*8 N, LDT, LDVL, LDVR, MM, M, LDWORK, INFO
  INTEGER*8 WORK1(*)
  LOGICAL*8 SELECT(*)
  DOUBLE PRECISION T(LDT,*), VL(LDVL,*), VR(LDVR,*), S(*), SEP(*), WORK(LDWORK,*)

F95 INTERFACE

  SUBROUTINE TRSNA( JOB, HOWMNY, SELECT, [N], T, [LDT], VL, [LDVL], 
 *       VR, [LDVR], S, SEP, MM, M, [WORK], [LDWORK], [WORK1], [INFO])
  CHARACTER(LEN=1) :: JOB, HOWMNY
  INTEGER :: N, LDT, LDVL, LDVR, MM, M, LDWORK, INFO
  INTEGER, DIMENSION(:) :: WORK1
  LOGICAL, DIMENSION(:) :: SELECT
  REAL(8), DIMENSION(:) :: S, SEP
  REAL(8), DIMENSION(:,:) :: T, VL, VR, WORK
  SUBROUTINE TRSNA_64( JOB, HOWMNY, SELECT, [N], T, [LDT], VL, [LDVL], 
 *       VR, [LDVR], S, SEP, MM, M, [WORK], [LDWORK], [WORK1], [INFO])
  CHARACTER(LEN=1) :: JOB, HOWMNY
  INTEGER(8) :: N, LDT, LDVL, LDVR, MM, M, LDWORK, INFO
  INTEGER(8), DIMENSION(:) :: WORK1
  LOGICAL(8), DIMENSION(:) :: SELECT
  REAL(8), DIMENSION(:) :: S, SEP
  REAL(8), DIMENSION(:,:) :: T, VL, VR, WORK

C INTERFACE

#include <sunperf.h>

void dtrsna(char job, char howmny, logical *select, int n, double *t, int ldt, double *vl, int ldvl, double *vr, int ldvr, double *s, double *sep, int mm, int *m, int ldwork, int *info);

void dtrsna_64(char job, char howmny, logical *select, long n, double *t, long ldt, double *vl, long ldvl, double *vr, long ldvr, double *s, double *sep, long mm, long *m, long ldwork, long *info);


PURPOSE

dtrsna estimates reciprocal condition numbers for specified eigenvalues and/or right eigenvectors of a real upper quasi-triangular matrix T (or of any matrix Q*T*Q**T with Q orthogonal).

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 elements equal and its off-diagonal elements of opposite sign.


ARGUMENTS


FURTHER DETAILS

The reciprocal of the condition number of an eigenvalue lambda is defined as

        S(lambda)  = |v'*u| / (norm(u)*norm(v))

where u and v are the right and left eigenvectors of T corresponding to lambda; v' denotes the conjugate-transpose of v, and norm(u) denotes the Euclidean norm. These reciprocal condition numbers always lie between zero (very badly conditioned) and one (very well conditioned). If n = 1, S(lambda) is defined to be 1.

An approximate error bound for a computed eigenvalue W(i) is given by

                    EPS * norm(T) / S(i)

where EPS is the machine precision.

The reciprocal of the condition number of the right eigenvector u corresponding to lambda is defined as follows. Suppose

            T  = ( lambda  c  )
                (   0    T22 )

Then the reciprocal condition number is

        SEP( lambda, T22 )  = sigma-min( T22 - lambda*I )

where sigma-min denotes the smallest singular value. We approximate the smallest singular value by the reciprocal of an estimate of the one-norm of the inverse of T22 - lambda*I. If n = 1, SEP(1) is defined to be abs(T(1,1)).

An approximate error bound for a computed right eigenvector VR(i) is given by

                    EPS * norm(T) / SEP(i)