*nix Documentation Project
·  Home
 +   man pages
·  Linux HOWTOs
·  FreeBSD Tips
·  *niX Forums

  man pages->IRIX man pages -> complib/ztrsna (3)              
Title
Content
Arch
Section
 

Contents


ZTRSNA(3F)							    ZTRSNA(3F)


NAME    [Toc]    [Back]

     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    [Toc]    [Back]

     SUBROUTINE	ZTRSNA(	JOB, HOWMNY, SELECT, N,	T, LDT,	VL, LDVL, VR, LDVR, S,
			SEP, MM, M, WORK, LDWORK, RWORK, INFO )

	 CHARACTER	HOWMNY,	JOB

	 INTEGER	INFO, LDT, LDVL, LDVR, LDWORK, M, MM, N

	 LOGICAL	SELECT(	* )

	 DOUBLE		PRECISION RWORK( * ), S( * ), SEP( * )

	 COMPLEX*16	T( LDT,	* ), VL( LDVL, * ), VR(	LDVR, *	), WORK(
			LDWORK,	* )

PURPOSE    [Toc]    [Back]

     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    [Toc]    [Back]

     JOB     (input) CHARACTER*1
	     Specifies whether condition numbers are required for eigenvalues
	     (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) CHARACTER*1
	     = 'A': compute condition numbers for all eigenpairs;
	     = 'S': compute condition numbers for selected eigenpairs
	     specified by the array SELECT.

     SELECT  (input) LOGICAL array, dimension (N)
	     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) INTEGER
	     The order of the matrix T.	N >= 0.

     T	     (input) COMPLEX*16	array, dimension (LDT,N)
	     The upper triangular matrix T.





									Page 1






ZTRSNA(3F)							    ZTRSNA(3F)



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

     VL	     (input) COMPLEX*16	array, dimension (LDVL,M)
	     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 ZHSEIN or ZTREVC.
	     If	JOB = 'V', VL is not referenced.

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

     VR	     (input) COMPLEX*16	array, dimension (LDVR,M)
	     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 ZHSEIN or ZTREVC.
	     If	JOB = 'V', VR is not referenced.

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

     S	     (output) DOUBLE PRECISION array, dimension	(MM)
	     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) DOUBLE PRECISION array, dimension	(MM)
	     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) INTEGER
	     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) INTEGER
	     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) COMPLEX*16 array, dimension (LDWORK,N+1)
	     If	JOB = 'E', WORK	is not referenced.






									Page 2






ZTRSNA(3F)							    ZTRSNA(3F)



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

     RWORK   (workspace) DOUBLE	PRECISION array, dimension (N)
	     If	JOB = 'E', RWORK is not	referenced.

     INFO    (output) INTEGER
	     = 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
     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)
ZTRSNA(3F)							    ZTRSNA(3F)


NAME    [Toc]    [Back]

     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    [Toc]    [Back]

     SUBROUTINE	ZTRSNA(	JOB, HOWMNY, SELECT, N,	T, LDT,	VL, LDVL, VR, LDVR, S,
			SEP, MM, M, WORK, LDWORK, RWORK, INFO )

	 CHARACTER	HOWMNY,	JOB

	 INTEGER	INFO, LDT, LDVL, LDVR, LDWORK, M, MM, N

	 LOGICAL	SELECT(	* )

	 DOUBLE		PRECISION RWORK( * ), S( * ), SEP( * )

	 COMPLEX*16	T( LDT,	* ), VL( LDVL, * ), VR(	LDVR, *	), WORK(
			LDWORK,	* )

PURPOSE    [Toc]    [Back]

     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    [Toc]    [Back]

     JOB     (input) CHARACTER*1
	     Specifies whether condition numbers are required for eigenvalues
	     (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) CHARACTER*1
	     = 'A': compute condition numbers for all eigenpairs;
	     = 'S': compute condition numbers for selected eigenpairs
	     specified by the array SELECT.

     SELECT  (input) LOGICAL array, dimension (N)
	     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) INTEGER
	     The order of the matrix T.	N >= 0.

     T	     (input) COMPLEX*16	array, dimension (LDT,N)
	     The upper triangular matrix T.





									Page 1






ZTRSNA(3F)							    ZTRSNA(3F)



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

     VL	     (input) COMPLEX*16	array, dimension (LDVL,M)
	     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 ZHSEIN or ZTREVC.
	     If	JOB = 'V', VL is not referenced.

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

     VR	     (input) COMPLEX*16	array, dimension (LDVR,M)
	     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 ZHSEIN or ZTREVC.
	     If	JOB = 'V', VR is not referenced.

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

     S	     (output) DOUBLE PRECISION array, dimension	(MM)
	     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) DOUBLE PRECISION array, dimension	(MM)
	     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) INTEGER
	     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) INTEGER
	     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) COMPLEX*16 array, dimension (LDWORK,N+1)
	     If	JOB = 'E', WORK	is not referenced.






									Page 2






ZTRSNA(3F)							    ZTRSNA(3F)



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

     RWORK   (workspace) DOUBLE	PRECISION array, dimension (N)
	     If	JOB = 'E', RWORK is not	referenced.

     INFO    (output) INTEGER
	     = 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
     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)


									PPPPaaaaggggeeee 3333
[ Back ]
 Similar pages
Name OS Title
sdisna IRIX compute the reciprocal condition numbers for the eigenvectors of a real symmetric or complex Hermitian matrix
ddisna IRIX compute the reciprocal condition numbers for the eigenvectors of a real symmetric or complex Hermitian matrix
cgtcon IRIX estimate the reciprocal of the condition number of a complex tridiagonal matrix A using the LU factorization a
zhecon IRIX estimate the reciprocal of the condition number of a complex Hermitian matrix A using the factorization A = U*
zgtcon IRIX estimate the reciprocal of the condition number of a complex tridiagonal matrix A using the LU factorization a
checon IRIX estimate the reciprocal of the condition number of a complex Hermitian matrix A using the factorization A = U*
cspcon IRIX estimate the reciprocal of the condition number (in the 1-norm) of a complex symmetric packed matrix A using t
zspcon IRIX estimate the reciprocal of the condition number (in the 1-norm) of a complex symmetric packed matrix A using t
csycon IRIX estimate the reciprocal of the condition number (in the 1-norm) of a complex symmetric matrix A using the fact
zhpcon IRIX estimate the reciprocal of the condition number of a complex Hermitian packed matrix A using the factorization
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service