ztrsna


NAME

ztrsna - estimate reciprocal condition numbers for specified eigenvalues and/or right eigenvectors of a complex upper triangular matrix T (or of any matrix Q*T*Q**H with Q unitary)


SYNOPSIS

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

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
  COMPLEX(8), DIMENSION(:,:) :: T, VL, VR, WORK
  INTEGER :: N, LDT, LDVL, LDVR, MM, M, LDWORK, INFO
  LOGICAL, DIMENSION(:) :: SELECT
  REAL(8), DIMENSION(:) :: S, SEP, WORK1
 
  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
  COMPLEX(8), DIMENSION(:,:) :: T, VL, VR, WORK
  INTEGER(8) :: N, LDT, LDVL, LDVR, MM, M, LDWORK, INFO
  LOGICAL(8), DIMENSION(:) :: SELECT
  REAL(8), DIMENSION(:) :: S, SEP, WORK1
 

C INTERFACE

#include <sunperf.h>

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

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


PURPOSE

ztrsna estimates reciprocal condition numbers for specified eigenvalues and/or right eigenvectors of a complex upper triangular matrix T (or of any matrix Q*T*Q**H with Q unitary).


ARGUMENTS

* JOB (input)
Specifies whether condition numbers are required for eigenvalues (S) or eigenvectors (SEP):

* HOWMNY (input)

* SELECT (input)
If HOWMNY = 'S', SELECT specifies the eigenpairs for which condition numbers are required. To select condition numbers for the j-th eigenpair, SELECT(j) must be set to .TRUE.. If HOWMNY = 'A', SELECT is not referenced.

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

* T (input)
The upper triangular matrix T.

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

* VL (input)
If JOB = 'E' or 'B', VL must contain left eigenvectors of T (or of any Q*T*Q**H with Q unitary), corresponding to the eigenpairs specified by HOWMNY and SELECT. The eigenvectors must be stored in consecutive columns of VL, as returned by CHSEIN or CTREVC. If JOB = 'V', VL is not referenced.

* LDVL (input)
The leading dimension of the array VL. LDVL >= 1; and if JOB = 'E' or 'B', LDVL >= N.

* VR (input)
If JOB = 'E' or 'B', VR must contain right eigenvectors of T (or of any Q*T*Q**H with Q unitary), corresponding to the eigenpairs specified by HOWMNY and SELECT. The eigenvectors must be stored in consecutive columns of VR, as returned by CHSEIN or CTREVC. If JOB = 'V', VR is not referenced.

* LDVR (input)
The leading dimension of the array VR. LDVR >= 1; and if JOB = 'E' or 'B', LDVR >= N.

* S (output)
If JOB = 'E' or 'B', the reciprocal condition numbers of the selected eigenvalues, stored in consecutive elements of the array. Thus S(j), SEP(j), and the j-th columns of VL and VR all correspond to the same eigenpair (but not in general the j-th eigenpair, unless all eigenpairs are selected). If JOB = 'V', S is not referenced.

* SEP (output)
If JOB = 'V' or 'B', the estimated reciprocal condition numbers of the selected eigenvectors, stored in consecutive elements of the array. If JOB = 'E', SEP is not referenced.

* MM (input)
The number of elements in the arrays S (if JOB = 'E' or 'B') and/or SEP (if JOB = 'V' or 'B'). MM >= M.

* M (output)
The number of elements of the arrays S and/or SEP actually used to store the estimated condition numbers. If HOWMNY = 'A', M is set to N.

* WORK (workspace)
If JOB = 'E', WORK is not referenced.

* LDWORK (input)
The leading dimension of the array WORK. LDWORK >= 1; and if JOB = 'V' or 'B', LDWORK >= N.

* WORK1 (workspace)
If JOB = 'E', WORK1 is not referenced.

* INFO (output)