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

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

Contents


ZHBGV(3F)							     ZHBGV(3F)


NAME    [Toc]    [Back]

     ZHBGV - compute all the eigenvalues, and optionally, the eigenvectors of
     a complex generalized Hermitian-definite banded eigenproblem, of the form
     A*x=(lambda)*B*x

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	ZHBGV( JOBZ, UPLO, N, KA, KB, AB, LDAB,	BB, LDBB, W, Z,	LDZ,
		       WORK, RWORK, INFO )

	 CHARACTER     JOBZ, UPLO

	 INTEGER       INFO, KA, KB, LDAB, LDBB, LDZ, N

	 DOUBLE	       PRECISION RWORK(	* ), W(	* )

	 COMPLEX*16    AB( LDAB, * ), BB( LDBB,	* ), WORK( * ),	Z( LDZ,	* )

PURPOSE    [Toc]    [Back]

     ZHBGV computes all	the eigenvalues, and optionally, the eigenvectors of a
     complex generalized Hermitian-definite banded eigenproblem, of the	form
     A*x=(lambda)*B*x. Here A and B are	assumed	to be Hermitian	and banded,
     and B is also positive definite.

ARGUMENTS    [Toc]    [Back]

     JOBZ    (input) CHARACTER*1
	     = 'N':  Compute eigenvalues only;
	     = 'V':  Compute eigenvalues and eigenvectors.

     UPLO    (input) CHARACTER*1
	     = 'U':  Upper triangles of	A and B	are stored;
	     = 'L':  Lower triangles of	A and B	are stored.

     N	     (input) INTEGER
	     The order of the matrices A and B.	 N >= 0.

     KA	     (input) INTEGER
	     The number	of superdiagonals of the matrix	A if UPLO = 'U', or
	     the number	of subdiagonals	if UPLO	= 'L'. KA >= 0.

     KB	     (input) INTEGER
	     The number	of superdiagonals of the matrix	B if UPLO = 'U', or
	     the number	of subdiagonals	if UPLO	= 'L'. KB >= 0.

     AB	     (input/output) COMPLEX*16 array, dimension	(LDAB, N)
	     On	entry, the upper or lower triangle of the Hermitian band
	     matrix A, stored in the first ka+1	rows of	the array.  The	j-th
	     column of A is stored in the j-th column of the array AB as
	     follows:  if UPLO = 'U', AB(ka+1+i-j,j) = A(i,j) for max(1,jka)<=i<=j;
	if UPLO	= 'L', AB(1+i-j,j)    =	A(i,j) for
	     j<=i<=min(n,j+ka).




									Page 1






ZHBGV(3F)							     ZHBGV(3F)



	     On	exit, the contents of AB are destroyed.

     LDAB    (input) INTEGER
	     The leading dimension of the array	AB.  LDAB >= KA+1.

     BB	     (input/output) COMPLEX*16 array, dimension	(LDBB, N)
	     On	entry, the upper or lower triangle of the Hermitian band
	     matrix B, stored in the first kb+1	rows of	the array.  The	j-th
	     column of B is stored in the j-th column of the array BB as
	     follows:  if UPLO = 'U', BB(kb+1+i-j,j) = B(i,j) for max(1,jkb)<=i<=j;
	if UPLO	= 'L', BB(1+i-j,j)    =	B(i,j) for
	     j<=i<=min(n,j+kb).

	     On	exit, the factor S from	the split Cholesky factorization B =
	     S**H*S, as	returned by ZPBSTF.

     LDBB    (input) INTEGER
	     The leading dimension of the array	BB.  LDBB >= KB+1.

     W	     (output) DOUBLE PRECISION array, dimension	(N)
	     If	INFO = 0, the eigenvalues in ascending order.

     Z	     (output) COMPLEX*16 array,	dimension (LDZ,	N)
	     If	JOBZ = 'V', then if INFO = 0, Z	contains the matrix Z of
	     eigenvectors, with	the i-th column	of Z holding the eigenvector
	     associated	with W(i). The eigenvectors are	normalized so that
	     Z**H*B*Z =	I.  If JOBZ = 'N', then	Z is not referenced.

     LDZ     (input) INTEGER
	     The leading dimension of the array	Z.  LDZ	>= 1, and if JOBZ =
	     'V', LDZ >= N.

     WORK    (workspace) COMPLEX*16 array, dimension (N)

     RWORK   (workspace) DOUBLE	PRECISION array, dimension (3*N)

     INFO    (output) INTEGER
	     = 0:  successful exit
	     < 0:  if INFO = -i, the i-th argument had an illegal value
	     > 0:  if INFO = i,	and i is:
	     <=	N:  the	algorithm failed to converge:  i off-diagonal elements
	     of	an intermediate	tridiagonal form did not converge to zero; >
	     N:	  if INFO = N +	i, for 1 <= i <= N, then ZPBSTF
	     returned INFO = i:	B is not positive definite.  The factorization
	     of	B could	not be completed and no	eigenvalues or eigenvectors
	     were computed.
ZHBGV(3F)							     ZHBGV(3F)


NAME    [Toc]    [Back]

     ZHBGV - compute all the eigenvalues, and optionally, the eigenvectors of
     a complex generalized Hermitian-definite banded eigenproblem, of the form
     A*x=(lambda)*B*x

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	ZHBGV( JOBZ, UPLO, N, KA, KB, AB, LDAB,	BB, LDBB, W, Z,	LDZ,
		       WORK, RWORK, INFO )

	 CHARACTER     JOBZ, UPLO

	 INTEGER       INFO, KA, KB, LDAB, LDBB, LDZ, N

	 DOUBLE	       PRECISION RWORK(	* ), W(	* )

	 COMPLEX*16    AB( LDAB, * ), BB( LDBB,	* ), WORK( * ),	Z( LDZ,	* )

PURPOSE    [Toc]    [Back]

     ZHBGV computes all	the eigenvalues, and optionally, the eigenvectors of a
     complex generalized Hermitian-definite banded eigenproblem, of the	form
     A*x=(lambda)*B*x. Here A and B are	assumed	to be Hermitian	and banded,
     and B is also positive definite.

ARGUMENTS    [Toc]    [Back]

     JOBZ    (input) CHARACTER*1
	     = 'N':  Compute eigenvalues only;
	     = 'V':  Compute eigenvalues and eigenvectors.

     UPLO    (input) CHARACTER*1
	     = 'U':  Upper triangles of	A and B	are stored;
	     = 'L':  Lower triangles of	A and B	are stored.

     N	     (input) INTEGER
	     The order of the matrices A and B.	 N >= 0.

     KA	     (input) INTEGER
	     The number	of superdiagonals of the matrix	A if UPLO = 'U', or
	     the number	of subdiagonals	if UPLO	= 'L'. KA >= 0.

     KB	     (input) INTEGER
	     The number	of superdiagonals of the matrix	B if UPLO = 'U', or
	     the number	of subdiagonals	if UPLO	= 'L'. KB >= 0.

     AB	     (input/output) COMPLEX*16 array, dimension	(LDAB, N)
	     On	entry, the upper or lower triangle of the Hermitian band
	     matrix A, stored in the first ka+1	rows of	the array.  The	j-th
	     column of A is stored in the j-th column of the array AB as
	     follows:  if UPLO = 'U', AB(ka+1+i-j,j) = A(i,j) for max(1,jka)<=i<=j;
	if UPLO	= 'L', AB(1+i-j,j)    =	A(i,j) for
	     j<=i<=min(n,j+ka).




									Page 1






ZHBGV(3F)							     ZHBGV(3F)



	     On	exit, the contents of AB are destroyed.

     LDAB    (input) INTEGER
	     The leading dimension of the array	AB.  LDAB >= KA+1.

     BB	     (input/output) COMPLEX*16 array, dimension	(LDBB, N)
	     On	entry, the upper or lower triangle of the Hermitian band
	     matrix B, stored in the first kb+1	rows of	the array.  The	j-th
	     column of B is stored in the j-th column of the array BB as
	     follows:  if UPLO = 'U', BB(kb+1+i-j,j) = B(i,j) for max(1,jkb)<=i<=j;
	if UPLO	= 'L', BB(1+i-j,j)    =	B(i,j) for
	     j<=i<=min(n,j+kb).

	     On	exit, the factor S from	the split Cholesky factorization B =
	     S**H*S, as	returned by ZPBSTF.

     LDBB    (input) INTEGER
	     The leading dimension of the array	BB.  LDBB >= KB+1.

     W	     (output) DOUBLE PRECISION array, dimension	(N)
	     If	INFO = 0, the eigenvalues in ascending order.

     Z	     (output) COMPLEX*16 array,	dimension (LDZ,	N)
	     If	JOBZ = 'V', then if INFO = 0, Z	contains the matrix Z of
	     eigenvectors, with	the i-th column	of Z holding the eigenvector
	     associated	with W(i). The eigenvectors are	normalized so that
	     Z**H*B*Z =	I.  If JOBZ = 'N', then	Z is not referenced.

     LDZ     (input) INTEGER
	     The leading dimension of the array	Z.  LDZ	>= 1, and if JOBZ =
	     'V', LDZ >= N.

     WORK    (workspace) COMPLEX*16 array, dimension (N)

     RWORK   (workspace) DOUBLE	PRECISION array, dimension (3*N)

     INFO    (output) INTEGER
	     = 0:  successful exit
	     < 0:  if INFO = -i, the i-th argument had an illegal value
	     > 0:  if INFO = i,	and i is:
	     <=	N:  the	algorithm failed to converge:  i off-diagonal elements
	     of	an intermediate	tridiagonal form did not converge to zero; >
	     N:	  if INFO = N +	i, for 1 <= i <= N, then ZPBSTF
	     returned INFO = i:	B is not positive definite.  The factorization
	     of	B could	not be completed and no	eigenvalues or eigenvectors
	     were computed.


									PPPPaaaaggggeeee 2222
[ Back ]
 Similar pages
Name OS Title
zhpgv IRIX a complex generalized Hermitian-definite eigenproblem, of the form A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x
chegv IRIX a complex generalized Hermitian-definite eigenproblem, of the form A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x
zhegv IRIX a complex generalized Hermitian-definite eigenproblem, of the form A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x
chpgv IRIX a complex generalized Hermitian-definite eigenproblem, of the form A*x=(lambda)*B*x, A*Bx=(lambda)*x, or B*A*x
dsbgv IRIX a real generalized symmetric-definite banded eigenproblem, of the form A*x=(lambda)*B*x
ssbgv IRIX a real generalized symmetric-definite banded eigenproblem, of the form A*x=(lambda)*B*x
zhegs2 IRIX reduce a complex Hermitian-definite generalized eigenproblem to standard form
zhegst IRIX reduce a complex Hermitian-definite generalized eigenproblem to standard form
chegs2 IRIX reduce a complex Hermitian-definite generalized eigenproblem to standard form
chegst IRIX reduce a complex Hermitian-definite generalized eigenproblem to standard form
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service