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

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

Contents


CLAED7(3F)							    CLAED7(3F)


NAME    [Toc]    [Back]

     CLAED7 - compute the updated eigensystem of a diagonal matrix after
     modification by a rank-one	symmetric matrix

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	CLAED7(	N, CUTPNT, QSIZ, TLVLS,	CURLVL,	CURPBM,	D, Q, LDQ,
			RHO, INDXQ, QSTORE, QPTR, PRMPTR, PERM,	GIVPTR,
			GIVCOL,	GIVNUM,	WORK, RWORK, IWORK, INFO )

	 INTEGER	CURLVL,	CURPBM,	CUTPNT,	INFO, LDQ, N, QSIZ, TLVLS

	 REAL		RHO

	 INTEGER	GIVCOL(	2, * ),	GIVPTR(	* ), INDXQ( * ), IWORK(	* ),
			PERM( *	), PRMPTR( * ),	QPTR( *	)

	 REAL		D( * ),	GIVNUM(	2, * ),	QSTORE(	* ), RWORK( * )

	 COMPLEX	Q( LDQ,	* ), WORK( * )

PURPOSE    [Toc]    [Back]

     CLAED7 computes the updated eigensystem of	a diagonal matrix after
     modification by a rank-one	symmetric matrix. This routine is used only
     for the eigenproblem which	requires all eigenvalues and optionally
     eigenvectors of a dense or	banded Hermitian matrix	that has been reduced
     to	tridiagonal form.

       T = Q(in) ( D(in) + RHO * Z*Z' )	Q'(in) = Q(out)	* D(out) * Q'(out)

       where Z = Q'u, u	is a vector of length N	with ones in the
       CUTPNT and CUTPNT + 1 th	elements and zeros elsewhere.

	The eigenvectors of the	original matrix	are stored in Q, and the
	eigenvalues are	in D.  The algorithm consists of three stages:

	   The first stage consists of deflating the size of the problem
	   when	there are multiple eigenvalues or if there is a	zero in
	   the Z vector.  For each such	occurence the dimension	of the
	   secular equation problem is reduced by one.	This stage is
	   performed by	the routine SLAED2.

	   The second stage consists of	calculating the	updated
	   eigenvalues.	This is	done by	finding	the roots of the secular
	   equation via	the routine SLAED4 (as called by SLAED3).
	   This	routine	also calculates	the eigenvectors of the	current
	   problem.

	   The final stage consists of computing the updated eigenvectors
	   directly using the updated eigenvalues.  The	eigenvectors for
	   the current problem are multiplied with the eigenvectors from
	   the overall problem.




									Page 1






CLAED7(3F)							    CLAED7(3F)


ARGUMENTS    [Toc]    [Back]

     N	    (input) INTEGER
	    The	dimension of the symmetric tridiagonal matrix.	N >= 0.

	    CUTPNT (input) INTEGER Contains the	location of the	last
	    eigenvalue in the leading sub-matrix.  min(1,N) <= CUTPNT <= N.

     QSIZ   (input) INTEGER
	    The	dimension of the unitary matrix	used to	reduce the full	matrix
	    to tridiagonal form.  QSIZ >= N.

     TLVLS  (input) INTEGER
	    The	total number of	merging	levels in the overall divide and
	    conquer tree.

	    CURLVL (input) INTEGER The current level in	the overall merge
	    routine, 0 <= curlvl <= tlvls.

	    CURPBM (input) INTEGER The current problem in the current level in
	    the	overall	merge routine (counting	from upper left	to lower
	    right).

     D	    (input/output) REAL	array, dimension (N)
	    On entry, the eigenvalues of the rank-1-perturbed matrix.  On
	    exit, the eigenvalues of the repaired matrix.

     Q	    (input/output) COMPLEX array, dimension (LDQ,N)
	    On entry, the eigenvectors of the rank-1-perturbed matrix.	On
	    exit, the eigenvectors of the repaired tridiagonal matrix.

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

     RHO    (input) REAL
	    Contains the subdiagonal element used to create the	rank-1
	    modification.

     INDXQ  (output) INTEGER array, dimension (N)
	    This contains the permutation which	will reintegrate the
	    subproblem just solved back	into sorted order, ie. D( INDXQ( I =
	    1, N ) ) will be in	ascending order.

     IWORK  (workspace)	INTEGER	array, dimension (4*N)

     RWORK  (workspace)	REAL array,
	    dimension (3*N+2*QSIZ*N)

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

	    QSTORE (input/output) REAL array, dimension	(N**2+1) Stores
	    eigenvectors of submatrices	encountered during divide and conquer,
	    packed together. QPTR points to beginning of the submatrices.



									Page 2






CLAED7(3F)							    CLAED7(3F)



     QPTR   (input/output) INTEGER array, dimension (N+2)
	    List of indices pointing to	beginning of submatrices stored	in
	    QSTORE. The	submatrices are	numbered starting at the bottom	left
	    of the divide and conquer tree, from left to right and bottom to
	    top.

	    PRMPTR (input) INTEGER array, dimension (N lg N) Contains a	list
	    of pointers	which indicate where in	PERM a level's permutation is
	    stored.  PRMPTR(i+1) - PRMPTR(i) indicates the size	of the
	    permutation	and also the size of the full, non-deflated problem.

     PERM   (input) INTEGER array, dimension (N	lg N)
	    Contains the permutations (from deflation and sorting) to be
	    applied to each eigenblock.

	    GIVPTR (input) INTEGER array, dimension (N lg N) Contains a	list
	    of pointers	which indicate where in	GIVCOL a level's Givens
	    rotations are stored.  GIVPTR(i+1) - GIVPTR(i) indicates the
	    number of Givens rotations.

	    GIVCOL (input) INTEGER array, dimension (2,	N lg N)	Each pair of
	    numbers indicates a	pair of	columns	to take	place in a Givens
	    rotation.

	    GIVNUM (input) REAL	array, dimension (2, N lg N) Each number
	    indicates the S value to be	used in	the corresponding Givens
	    rotation.

     INFO   (output) INTEGER
	    = 0:  successful exit.
	    < 0:  if INFO = -i,	the i-th argument had an illegal value.
	    > 0:  if INFO = 1, an eigenvalue did not converge
CLAED7(3F)							    CLAED7(3F)


NAME    [Toc]    [Back]

     CLAED7 - compute the updated eigensystem of a diagonal matrix after
     modification by a rank-one	symmetric matrix

SYNOPSIS    [Toc]    [Back]

     SUBROUTINE	CLAED7(	N, CUTPNT, QSIZ, TLVLS,	CURLVL,	CURPBM,	D, Q, LDQ,
			RHO, INDXQ, QSTORE, QPTR, PRMPTR, PERM,	GIVPTR,
			GIVCOL,	GIVNUM,	WORK, RWORK, IWORK, INFO )

	 INTEGER	CURLVL,	CURPBM,	CUTPNT,	INFO, LDQ, N, QSIZ, TLVLS

	 REAL		RHO

	 INTEGER	GIVCOL(	2, * ),	GIVPTR(	* ), INDXQ( * ), IWORK(	* ),
			PERM( *	), PRMPTR( * ),	QPTR( *	)

	 REAL		D( * ),	GIVNUM(	2, * ),	QSTORE(	* ), RWORK( * )

	 COMPLEX	Q( LDQ,	* ), WORK( * )

PURPOSE    [Toc]    [Back]

     CLAED7 computes the updated eigensystem of	a diagonal matrix after
     modification by a rank-one	symmetric matrix. This routine is used only
     for the eigenproblem which	requires all eigenvalues and optionally
     eigenvectors of a dense or	banded Hermitian matrix	that has been reduced
     to	tridiagonal form.

       T = Q(in) ( D(in) + RHO * Z*Z' )	Q'(in) = Q(out)	* D(out) * Q'(out)

       where Z = Q'u, u	is a vector of length N	with ones in the
       CUTPNT and CUTPNT + 1 th	elements and zeros elsewhere.

	The eigenvectors of the	original matrix	are stored in Q, and the
	eigenvalues are	in D.  The algorithm consists of three stages:

	   The first stage consists of deflating the size of the problem
	   when	there are multiple eigenvalues or if there is a	zero in
	   the Z vector.  For each such	occurence the dimension	of the
	   secular equation problem is reduced by one.	This stage is
	   performed by	the routine SLAED2.

	   The second stage consists of	calculating the	updated
	   eigenvalues.	This is	done by	finding	the roots of the secular
	   equation via	the routine SLAED4 (as called by SLAED3).
	   This	routine	also calculates	the eigenvectors of the	current
	   problem.

	   The final stage consists of computing the updated eigenvectors
	   directly using the updated eigenvalues.  The	eigenvectors for
	   the current problem are multiplied with the eigenvectors from
	   the overall problem.




									Page 1






CLAED7(3F)							    CLAED7(3F)


ARGUMENTS    [Toc]    [Back]

     N	    (input) INTEGER
	    The	dimension of the symmetric tridiagonal matrix.	N >= 0.

	    CUTPNT (input) INTEGER Contains the	location of the	last
	    eigenvalue in the leading sub-matrix.  min(1,N) <= CUTPNT <= N.

     QSIZ   (input) INTEGER
	    The	dimension of the unitary matrix	used to	reduce the full	matrix
	    to tridiagonal form.  QSIZ >= N.

     TLVLS  (input) INTEGER
	    The	total number of	merging	levels in the overall divide and
	    conquer tree.

	    CURLVL (input) INTEGER The current level in	the overall merge
	    routine, 0 <= curlvl <= tlvls.

	    CURPBM (input) INTEGER The current problem in the current level in
	    the	overall	merge routine (counting	from upper left	to lower
	    right).

     D	    (input/output) REAL	array, dimension (N)
	    On entry, the eigenvalues of the rank-1-perturbed matrix.  On
	    exit, the eigenvalues of the repaired matrix.

     Q	    (input/output) COMPLEX array, dimension (LDQ,N)
	    On entry, the eigenvectors of the rank-1-perturbed matrix.	On
	    exit, the eigenvectors of the repaired tridiagonal matrix.

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

     RHO    (input) REAL
	    Contains the subdiagonal element used to create the	rank-1
	    modification.

     INDXQ  (output) INTEGER array, dimension (N)
	    This contains the permutation which	will reintegrate the
	    subproblem just solved back	into sorted order, ie. D( INDXQ( I =
	    1, N ) ) will be in	ascending order.

     IWORK  (workspace)	INTEGER	array, dimension (4*N)

     RWORK  (workspace)	REAL array,
	    dimension (3*N+2*QSIZ*N)

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

	    QSTORE (input/output) REAL array, dimension	(N**2+1) Stores
	    eigenvectors of submatrices	encountered during divide and conquer,
	    packed together. QPTR points to beginning of the submatrices.



									Page 2






CLAED7(3F)							    CLAED7(3F)



     QPTR   (input/output) INTEGER array, dimension (N+2)
	    List of indices pointing to	beginning of submatrices stored	in
	    QSTORE. The	submatrices are	numbered starting at the bottom	left
	    of the divide and conquer tree, from left to right and bottom to
	    top.

	    PRMPTR (input) INTEGER array, dimension (N lg N) Contains a	list
	    of pointers	which indicate where in	PERM a level's permutation is
	    stored.  PRMPTR(i+1) - PRMPTR(i) indicates the size	of the
	    permutation	and also the size of the full, non-deflated problem.

     PERM   (input) INTEGER array, dimension (N	lg N)
	    Contains the permutations (from deflation and sorting) to be
	    applied to each eigenblock.

	    GIVPTR (input) INTEGER array, dimension (N lg N) Contains a	list
	    of pointers	which indicate where in	GIVCOL a level's Givens
	    rotations are stored.  GIVPTR(i+1) - GIVPTR(i) indicates the
	    number of Givens rotations.

	    GIVCOL (input) INTEGER array, dimension (2,	N lg N)	Each pair of
	    numbers indicates a	pair of	columns	to take	place in a Givens
	    rotation.

	    GIVNUM (input) REAL	array, dimension (2, N lg N) Each number
	    indicates the S value to be	used in	the corresponding Givens
	    rotation.

     INFO   (output) INTEGER
	    = 0:  successful exit.
	    < 0:  if INFO = -i,	the i-th argument had an illegal value.
	    > 0:  if INFO = 1, an eigenvalue did not converge


									PPPPaaaaggggeeee 3333
[ Back ]
 Similar pages
Name OS Title
dlaed4 IRIX rank-one modification to a diagonal matrix whose elements are given in the array d, and that D(i) < D(j) for i
slaed4 IRIX rank-one modification to a diagonal matrix whose elements are given in the array d, and that D(i) < D(j) for i
spr IRIX BLAS Level Two Symmetric Packed Matrix Rank 1 Update FORTRAN 77 SYNOPSIS subroutine dspr( uplo, n, alpha, x, i
syr2 IRIX BLAS Level Two (Symmetric/Hermitian)Matrix Rank 2 Update FORTRAN 77 SYNOPSIS subroutine dsyr2( uplo, n, alpha,
syr IRIX BLAS Level Two (Symmetric/Hermitian)Matrix Rank 1 Update FORTRAN 77 SYNOPSIS subroutine dsyr( uplo, n, alpha,
spr2 IRIX BLAS Level Two Symmetric Packed Matrix Rank 2 Update FORTRAN 77 SYNOPSIS subroutine dspr2( uplo, n, alpha, n,
csyr IRIX perform the symmetric rank 1 operation A := alpha*x*( x' ) + A,
zsyr IRIX perform the symmetric rank 1 operation A := alpha*x*( x' ) + A,
BANDR IRIX EISPACK routine. This subroutine reduces a REAL SYMMETRIC BAND matrix to a symmetric tridiagonal matrix using
TRED1 IRIX EISPACK routine. This subroutine reduces a REAL SYMMETRIC matrix to a symmetric tridiagonal matrix using ortho
Copyright © 2004-2005 DeniX Solutions SRL
newsletter delivery service