dtrsna man page on OpenIndiana

Man page or keyword search:  
man Server   20441 pages
apropos Keyword Search (all sections)
Output format
OpenIndiana logo
[printable version]

dtrsna(3P)		    Sun Performance Library		    dtrsna(3P)

NAME
       dtrsna  - estimate reciprocal condition numbers for specified eigenval‐
       ues 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, int *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, long *select, long n, double *t,
		 long ldt, double *vl, long ldvl, double *vr, long ldvr,  dou‐
		 ble  *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  DHSEQR),  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-diag‐
       onal elements of opposite sign.

ARGUMENTS
       JOB (input)
		 Specifies  whether  condition numbers are required for eigen‐
		 values (S) or eigenvectors (SEP):
		 = 'E': for eigenvalues only (S);
		 = 'V': for eigenvectors only (SEP);
		 = 'B': for both eigenvalues and eigenvectors (S and SEP).

       HOWMNY (input)
		 = 'A': compute condition numbers for all eigenpairs;
		 = 'S': compute	 condition  numbers  for  selected  eigenpairs
		 specified by the array SELECT.

       SELECT (input)
		 If  HOWMNY  =	'S', SELECT specifies the eigenpairs for which
		 condition numbers are required. To select  condition  numbers
		 for  the  eigenpair  corresponding to a real eigenvalue w(j),
		 SELECT(j) must be set to .TRUE.. To select condition  numbers
		 corresponding to a complex conjugate pair of eigenvalues w(j)
		 and w(j+1), either SELECT(j) or SELECT(j+1) or both, 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 quasi-triangular matrix T, in Schur canonical form.

       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**T with Q orthogonal), corresponding to  the
		 eigenpairs  specified	by HOWMNY and SELECT. The eigenvectors
		 must be stored in consecutive columns of VL, as  returned  by
		 DHSEIN or DTREVC.  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**T with Q orthogonal), corresponding to the
		 eigenpairs specified by HOWMNY and SELECT.  The  eigenvectors
		 must  be  stored in consecutive columns of VR, as returned by
		 DHSEIN or DTREVC.  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.	 For  a complex conjugate pair of eigenvalues two con‐
		 secutive elements of S are set to the same value. 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  num‐
		 bers of the selected eigenvectors, stored in consecutive ele‐
		 ments of the array. For a complex eigenvector two consecutive
		 elements of SEP are set to the same value. If the eigenvalues
		 cannot be reordered to compute SEP(j), SEP(j) is  set	to  0;
		 this  can  only occur when the true value would be very small
		 anyway.  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)
		 dimension(LDWORK,N+6) 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)
		 dimension(2*N) If JOB = 'E', WORK1 is not referenced.

       INFO (output)
		 = 0: successful exit
		 < 0: if INFO = -i, the i-th argument had an illegal value

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 cor‐
       responding 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)

				  6 Mar 2009			    dtrsna(3P)
[top]

List of man pages available for OpenIndiana

Copyright (c) for man pages and the logo by the respective OS vendor.

For those who want to learn more, the polarhome community provides shell access and support.

[legal] [privacy] [GNU] [policy] [cookies] [netiquette] [sponsors] [FAQ]
Tweet
Polarhome, production since 1999.
Member of Polarhome portal.
Based on Fawad Halim's script.
....................................................................
Vote for polarhome
Free Shell Accounts :: the biggest list on the net