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

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

Contents


DLAEIN(3F)							    DLAEIN(3F)


NAME    [Toc]    [Back]

     DLAEIN - use inverse iteration to find a right or left eigenvector
     corresponding to the eigenvalue (WR,WI) of	a real upper Hessenberg	matrix
     H

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	DLAEIN(	RIGHTV,	NOINIT,	N, H, LDH, WR, WI, VR, VI, B, LDB,
			WORK, EPS3, SMLNUM, BIGNUM, INFO )

	 LOGICAL	NOINIT,	RIGHTV

	 INTEGER	INFO, LDB, LDH,	N

	 DOUBLE		PRECISION BIGNUM, EPS3,	SMLNUM,	WI, WR

	 DOUBLE		PRECISION B( LDB, * ), H( LDH, * ), VI(	* ), VR( * ),
			WORK( *	)

PURPOSE    [Toc]    [Back]

     DLAEIN uses inverse iteration to find a right or left eigenvector
     corresponding to the eigenvalue (WR,WI) of	a real upper Hessenberg	matrix
     H.

ARGUMENTS    [Toc]    [Back]

     RIGHTV   (input) LOGICAL
	      =	.TRUE. : compute right eigenvector;
	      =	.FALSE.: compute left eigenvector.

     NOINIT   (input) LOGICAL
	      =	.TRUE. : no initial vector supplied in (VR,VI).
	      =	.FALSE.: initial vector	supplied in (VR,VI).

     N	     (input) INTEGER
	     The order of the matrix H.	 N >= 0.

     H	     (input) DOUBLE PRECISION array, dimension (LDH,N)
	     The upper Hessenberg matrix H.

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

     WR	     (input) DOUBLE PRECISION
	     WI	     (input) DOUBLE PRECISION The real and imaginary parts of
	     the eigenvalue of H whose corresponding right or left eigenvector
	     is	to be computed.

     VR	     (input/output) DOUBLE PRECISION array, dimension (N)
	     VI	     (input/output) DOUBLE PRECISION array, dimension (N) On
	     entry, if NOINIT =	.FALSE.	and WI = 0.0, VR must contain a	real
	     starting vector for inverse iteration using the real eigenvalue
	     WR; if NOINIT = .FALSE. and WI.ne.0.0, VR and VI must contain the



									Page 1






DLAEIN(3F)							    DLAEIN(3F)



	     real and imaginary	parts of a complex starting vector for inverse
	     iteration using the complex eigenvalue (WR,WI); otherwise VR and
	     VI	need not be set.  On exit, if WI = 0.0 (real eigenvalue), VR
	     contains the computed real	eigenvector; if	WI.ne.0.0 (complex
	     eigenvalue), VR and VI contain the	real and imaginary parts of
	     the computed complex eigenvector. The eigenvector is normalized
	     so	that the component of largest magnitude	has magnitude 1; here
	     the magnitude of a	complex	number (x,y) is	taken to be |x|	+ |y|.
	     VI	is not referenced if WI	= 0.0.

     B	     (workspace) DOUBLE	PRECISION array, dimension (LDB,N)

     LDB     (input) INTEGER
	     The leading dimension of the array	B.  LDB	>= N+1.

     WORK   (workspace)	DOUBLE PRECISION array,	dimension (N)

     EPS3    (input) DOUBLE PRECISION
	     A small machine-dependent value which is used to perturb close
	     eigenvalues, and to replace zero pivots.

     SMLNUM  (input) DOUBLE PRECISION
	     A machine-dependent value close to	the underflow threshold.

     BIGNUM  (input) DOUBLE PRECISION
	     A machine-dependent value close to	the overflow threshold.

     INFO    (output) INTEGER
	     = 0:  successful exit
	     = 1:  inverse iteration did not converge; VR is set to the	last
	     iterate, and so is	VI if WI.ne.0.0.
DLAEIN(3F)							    DLAEIN(3F)


NAME    [Toc]    [Back]

     DLAEIN - use inverse iteration to find a right or left eigenvector
     corresponding to the eigenvalue (WR,WI) of	a real upper Hessenberg	matrix
     H

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	DLAEIN(	RIGHTV,	NOINIT,	N, H, LDH, WR, WI, VR, VI, B, LDB,
			WORK, EPS3, SMLNUM, BIGNUM, INFO )

	 LOGICAL	NOINIT,	RIGHTV

	 INTEGER	INFO, LDB, LDH,	N

	 DOUBLE		PRECISION BIGNUM, EPS3,	SMLNUM,	WI, WR

	 DOUBLE		PRECISION B( LDB, * ), H( LDH, * ), VI(	* ), VR( * ),
			WORK( *	)

PURPOSE    [Toc]    [Back]

     DLAEIN uses inverse iteration to find a right or left eigenvector
     corresponding to the eigenvalue (WR,WI) of	a real upper Hessenberg	matrix
     H.

ARGUMENTS    [Toc]    [Back]

     RIGHTV   (input) LOGICAL
	      =	.TRUE. : compute right eigenvector;
	      =	.FALSE.: compute left eigenvector.

     NOINIT   (input) LOGICAL
	      =	.TRUE. : no initial vector supplied in (VR,VI).
	      =	.FALSE.: initial vector	supplied in (VR,VI).

     N	     (input) INTEGER
	     The order of the matrix H.	 N >= 0.

     H	     (input) DOUBLE PRECISION array, dimension (LDH,N)
	     The upper Hessenberg matrix H.

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

     WR	     (input) DOUBLE PRECISION
	     WI	     (input) DOUBLE PRECISION The real and imaginary parts of
	     the eigenvalue of H whose corresponding right or left eigenvector
	     is	to be computed.

     VR	     (input/output) DOUBLE PRECISION array, dimension (N)
	     VI	     (input/output) DOUBLE PRECISION array, dimension (N) On
	     entry, if NOINIT =	.FALSE.	and WI = 0.0, VR must contain a	real
	     starting vector for inverse iteration using the real eigenvalue
	     WR; if NOINIT = .FALSE. and WI.ne.0.0, VR and VI must contain the



									Page 1






DLAEIN(3F)							    DLAEIN(3F)



	     real and imaginary	parts of a complex starting vector for inverse
	     iteration using the complex eigenvalue (WR,WI); otherwise VR and
	     VI	need not be set.  On exit, if WI = 0.0 (real eigenvalue), VR
	     contains the computed real	eigenvector; if	WI.ne.0.0 (complex
	     eigenvalue), VR and VI contain the	real and imaginary parts of
	     the computed complex eigenvector. The eigenvector is normalized
	     so	that the component of largest magnitude	has magnitude 1; here
	     the magnitude of a	complex	number (x,y) is	taken to be |x|	+ |y|.
	     VI	is not referenced if WI	= 0.0.

     B	     (workspace) DOUBLE	PRECISION array, dimension (LDB,N)

     LDB     (input) INTEGER
	     The leading dimension of the array	B.  LDB	>= N+1.

     WORK   (workspace)	DOUBLE PRECISION array,	dimension (N)

     EPS3    (input) DOUBLE PRECISION
	     A small machine-dependent value which is used to perturb close
	     eigenvalues, and to replace zero pivots.

     SMLNUM  (input) DOUBLE PRECISION
	     A machine-dependent value close to	the underflow threshold.

     BIGNUM  (input) DOUBLE PRECISION
	     A machine-dependent value close to	the overflow threshold.

     INFO    (output) INTEGER
	     = 0:  successful exit
	     = 1:  inverse iteration did not converge; VR is set to the	last
	     iterate, and so is	VI if WI.ne.0.0.


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
zlaein IRIX use inverse iteration to find a right or left eigenvector corresponding to the eigenvalue W of a complex upper
claein IRIX use inverse iteration to find a right or left eigenvector corresponding to the eigenvalue W of a complex upper
shsein IRIX use inverse iteration to find specified right and/or left eigenvectors of a real upper Hessenberg matrix H
dhsein IRIX use inverse iteration to find specified right and/or left eigenvectors of a real upper Hessenberg matrix H
chsein IRIX use inverse iteration to find specified right and/or left eigenvectors of a complex upper Hessenberg matrix H
zhsein IRIX use inverse iteration to find specified right and/or left eigenvectors of a complex upper Hessenberg matrix H
sggbak IRIX form the right or left eigenvectors of a real generalized eigenvalue problem A*x = lambda*B*x, by backward tra
dggbak IRIX form the right or left eigenvectors of a real generalized eigenvalue problem A*x = lambda*B*x, by backward tra
zggbak IRIX form the right or left eigenvectors of a complex generalized eigenvalue problem A*x = lambda*B*x, by backward
cggbak IRIX form the right or left eigenvectors of a complex generalized eigenvalue problem A*x = lambda*B*x, by backward
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service