ctgsna


NAME

ctgsna - estimate reciprocal condition numbers for specified eigenvalues and/or eigenvectors of a matrix pair (A, B)


SYNOPSIS

  SUBROUTINE CTGSNA( JOB, HOWMNT, SELECT, N, A, LDA, B, LDB, VL, LDVL, 
 *      VR, LDVR, S, DIF, MM, M, WORK, LWORK, IWORK, INFO)
  CHARACTER * 1 JOB, HOWMNT
  COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*)
  INTEGER N, LDA, LDB, LDVL, LDVR, MM, M, LWORK, INFO
  INTEGER IWORK(*)
  LOGICAL SELECT(*)
  REAL S(*), DIF(*)
 
  SUBROUTINE CTGSNA_64( JOB, HOWMNT, SELECT, N, A, LDA, B, LDB, VL, 
 *      LDVL, VR, LDVR, S, DIF, MM, M, WORK, LWORK, IWORK, INFO)
  CHARACTER * 1 JOB, HOWMNT
  COMPLEX A(LDA,*), B(LDB,*), VL(LDVL,*), VR(LDVR,*), WORK(*)
  INTEGER*8 N, LDA, LDB, LDVL, LDVR, MM, M, LWORK, INFO
  INTEGER*8 IWORK(*)
  LOGICAL*8 SELECT(*)
  REAL S(*), DIF(*)
 

F95 INTERFACE

  SUBROUTINE TGSNA( JOB, HOWMNT, SELECT, [N], A, [LDA], B, [LDB], VL, 
 *       [LDVL], VR, [LDVR], S, DIF, MM, M, [WORK], [LWORK], [IWORK], 
 *       [INFO])
  CHARACTER(LEN=1) :: JOB, HOWMNT
  COMPLEX, DIMENSION(:) :: WORK
  COMPLEX, DIMENSION(:,:) :: A, B, VL, VR
  INTEGER :: N, LDA, LDB, LDVL, LDVR, MM, M, LWORK, INFO
  INTEGER, DIMENSION(:) :: IWORK
  LOGICAL, DIMENSION(:) :: SELECT
  REAL, DIMENSION(:) :: S, DIF
 
  SUBROUTINE TGSNA_64( JOB, HOWMNT, SELECT, [N], A, [LDA], B, [LDB], 
 *       VL, [LDVL], VR, [LDVR], S, DIF, MM, M, [WORK], [LWORK], [IWORK], 
 *       [INFO])
  CHARACTER(LEN=1) :: JOB, HOWMNT
  COMPLEX, DIMENSION(:) :: WORK
  COMPLEX, DIMENSION(:,:) :: A, B, VL, VR
  INTEGER(8) :: N, LDA, LDB, LDVL, LDVR, MM, M, LWORK, INFO
  INTEGER(8), DIMENSION(:) :: IWORK
  LOGICAL(8), DIMENSION(:) :: SELECT
  REAL, DIMENSION(:) :: S, DIF
 

C INTERFACE

#include <sunperf.h>

void ctgsna(char job, char howmnt, logical *select, int n, complex *a, int lda, complex *b, int ldb, complex *vl, int ldvl, complex *vr, int ldvr, float *s, float *dif, int mm, int *m, int *info);

void ctgsna_64(char job, char howmnt, logical *select, long n, complex *a, long lda, complex *b, long ldb, complex *vl, long ldvl, complex *vr, long ldvr, float *s, float *dif, long mm, long *m, long *info);


PURPOSE

ctgsna estimates reciprocal condition numbers for specified eigenvalues and/or eigenvectors of a matrix pair (A, B).

(A, B) must be in generalized Schur canonical form, that is, A and B are both upper triangular.


ARGUMENTS

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

* HOWMNT (input)

* SELECT (input)
If HOWMNT = 'S', SELECT specifies the eigenpairs for which condition numbers are required. To select condition numbers for the corresponding j-th eigenvalue and/or eigenvector, SELECT(j) must be set to .TRUE.. If HOWMNT = 'A', SELECT is not referenced.

* N (input)
The order of the square matrix pair (A, B). N >= 0.

* A (input)
The upper triangular matrix A in the pair (A,B).

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

* B (input)
The upper triangular matrix B in the pair (A, B).

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

* VL (input)
If JOB = 'E' or 'B', VL must contain left eigenvectors of (A, B), corresponding to the eigenpairs specified by HOWMNT and SELECT. The eigenvectors must be stored in consecutive columns of VL, as returned by CTGEVC. 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 (A, B), corresponding to the eigenpairs specified by HOWMNT and SELECT. The eigenvectors must be stored in consecutive columns of VR, as returned by CTGEVC. If JOB = 'V', VR is not referenced.

* LDVR (input)
The leading dimension of the array VR. LDVR >= 1; 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. If JOB = 'V', S is not referenced.

* DIF (output)
If JOB = 'V' or 'B', the estimated reciprocal condition numbers of the selected eigenvectors, stored in consecutive elements of the array. If the eigenvalues cannot be reordered to compute DIF(j), DIF(j) is set to 0; this can only occur when the true value would be very small anyway. For each eigenvalue/vector specified by SELECT, DIF stores a Frobenius norm-based estimate of Difl. If JOB = 'E', DIF is not referenced.

* MM (input)
The number of elements in the arrays S and DIF. MM >= M.

* M (output)
The number of elements of the arrays S and DIF used to store the specified condition numbers; for each selected eigenvalue one element is used. If HOWMNT = 'A', M is set to N.

* WORK (workspace)
If JOB = 'E', 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 JOB = 'V' or 'B', LWORK >= 2*N*N.

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

* INFO (output)