diff options
Diffstat (limited to 'SRC/chpevd.f')
-rw-r--r-- | SRC/chpevd.f | 285 |
1 files changed, 285 insertions, 0 deletions
diff --git a/SRC/chpevd.f b/SRC/chpevd.f new file mode 100644 index 00000000..bbb53503 --- /dev/null +++ b/SRC/chpevd.f @@ -0,0 +1,285 @@ + SUBROUTINE CHPEVD( JOBZ, UPLO, N, AP, W, Z, LDZ, WORK, LWORK, + $ RWORK, LRWORK, IWORK, LIWORK, INFO ) +* +* -- LAPACK driver routine (version 3.1) -- +* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. +* November 2006 +* +* .. Scalar Arguments .. + CHARACTER JOBZ, UPLO + INTEGER INFO, LDZ, LIWORK, LRWORK, LWORK, N +* .. +* .. Array Arguments .. + INTEGER IWORK( * ) + REAL RWORK( * ), W( * ) + COMPLEX AP( * ), WORK( * ), Z( LDZ, * ) +* .. +* +* Purpose +* ======= +* +* CHPEVD computes all the eigenvalues and, optionally, eigenvectors of +* a complex Hermitian matrix A in packed storage. If eigenvectors are +* desired, it uses a divide and conquer algorithm. +* +* The divide and conquer algorithm makes very mild assumptions about +* floating point arithmetic. It will work on machines with a guard +* digit in add/subtract, or on those binary machines without guard +* digits which subtract like the Cray X-MP, Cray Y-MP, Cray C-90, or +* Cray-2. It could conceivably fail on hexadecimal or decimal machines +* without guard digits, but we know of none. +* +* Arguments +* ========= +* +* JOBZ (input) CHARACTER*1 +* = 'N': Compute eigenvalues only; +* = 'V': Compute eigenvalues and eigenvectors. +* +* UPLO (input) CHARACTER*1 +* = 'U': Upper triangle of A is stored; +* = 'L': Lower triangle of A is stored. +* +* N (input) INTEGER +* The order of the matrix A. N >= 0. +* +* AP (input/output) COMPLEX array, dimension (N*(N+1)/2) +* On entry, the upper or lower triangle of the Hermitian matrix +* A, packed columnwise in a linear array. The j-th column of A +* is stored in the array AP as follows: +* if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j; +* if UPLO = 'L', AP(i + (j-1)*(2*n-j)/2) = A(i,j) for j<=i<=n. +* +* On exit, AP is overwritten by values generated during the +* reduction to tridiagonal form. If UPLO = 'U', the diagonal +* and first superdiagonal of the tridiagonal matrix T overwrite +* the corresponding elements of A, and if UPLO = 'L', the +* diagonal and first subdiagonal of T overwrite the +* corresponding elements of A. +* +* W (output) REAL array, dimension (N) +* If INFO = 0, the eigenvalues in ascending order. +* +* Z (output) COMPLEX array, dimension (LDZ, N) +* If JOBZ = 'V', then if INFO = 0, Z contains the orthonormal +* eigenvectors of the matrix A, with the i-th column of Z +* holding the eigenvector associated with W(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 >= max(1,N). +* +* WORK (workspace/output) COMPLEX array, dimension (MAX(1,LWORK)) +* On exit, if INFO = 0, WORK(1) returns the required LWORK. +* +* LWORK (input) INTEGER +* The dimension of array WORK. +* If N <= 1, LWORK must be at least 1. +* If JOBZ = 'N' and N > 1, LWORK must be at least N. +* If JOBZ = 'V' and N > 1, LWORK must be at least 2*N. +* +* If LWORK = -1, then a workspace query is assumed; the routine +* only calculates the required sizes of the WORK, RWORK and +* IWORK arrays, returns these values as the first entries of +* the WORK, RWORK and IWORK arrays, and no error message +* related to LWORK or LRWORK or LIWORK is issued by XERBLA. +* +* RWORK (workspace/output) REAL array, dimension (MAX(1,LRWORK)) +* On exit, if INFO = 0, RWORK(1) returns the required LRWORK. +* +* LRWORK (input) INTEGER +* The dimension of array RWORK. +* If N <= 1, LRWORK must be at least 1. +* If JOBZ = 'N' and N > 1, LRWORK must be at least N. +* If JOBZ = 'V' and N > 1, LRWORK must be at least +* 1 + 5*N + 2*N**2. +* +* If LRWORK = -1, then a workspace query is assumed; the +* routine only calculates the required sizes of the WORK, RWORK +* and IWORK arrays, returns these values as the first entries +* of the WORK, RWORK and IWORK arrays, and no error message +* related to LWORK or LRWORK or LIWORK is issued by XERBLA. +* +* IWORK (workspace/output) INTEGER array, dimension (MAX(1,LIWORK)) +* On exit, if INFO = 0, IWORK(1) returns the required LIWORK. +* +* LIWORK (input) INTEGER +* The dimension of array IWORK. +* If JOBZ = 'N' or N <= 1, LIWORK must be at least 1. +* If JOBZ = 'V' and N > 1, LIWORK must be at least 3 + 5*N. +* +* If LIWORK = -1, then a workspace query is assumed; the +* routine only calculates the required sizes of the WORK, RWORK +* and IWORK arrays, returns these values as the first entries +* of the WORK, RWORK and IWORK arrays, and no error message +* related to LWORK or LRWORK or LIWORK is issued by XERBLA. +* +* INFO (output) INTEGER +* = 0: successful exit +* < 0: if INFO = -i, the i-th argument had an illegal value. +* > 0: if INFO = i, the algorithm failed to converge; i +* off-diagonal elements of an intermediate tridiagonal +* form did not converge to zero. +* +* ===================================================================== +* +* .. Parameters .. + REAL ZERO, ONE + PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0 ) + COMPLEX CONE + PARAMETER ( CONE = ( 1.0E+0, 0.0E+0 ) ) +* .. +* .. Local Scalars .. + LOGICAL LQUERY, WANTZ + INTEGER IINFO, IMAX, INDE, INDRWK, INDTAU, INDWRK, + $ ISCALE, LIWMIN, LLRWK, LLWRK, LRWMIN, LWMIN + REAL ANRM, BIGNUM, EPS, RMAX, RMIN, SAFMIN, SIGMA, + $ SMLNUM +* .. +* .. External Functions .. + LOGICAL LSAME + REAL CLANHP, SLAMCH + EXTERNAL LSAME, CLANHP, SLAMCH +* .. +* .. External Subroutines .. + EXTERNAL CHPTRD, CSSCAL, CSTEDC, CUPMTR, SSCAL, SSTERF, + $ XERBLA +* .. +* .. Intrinsic Functions .. + INTRINSIC SQRT +* .. +* .. Executable Statements .. +* +* Test the input parameters. +* + WANTZ = LSAME( JOBZ, 'V' ) + LQUERY = ( LWORK.EQ.-1 .OR. LRWORK.EQ.-1 .OR. LIWORK.EQ.-1 ) +* + INFO = 0 + IF( .NOT.( WANTZ .OR. LSAME( JOBZ, 'N' ) ) ) THEN + INFO = -1 + ELSE IF( .NOT.( LSAME( UPLO, 'L' ) .OR. LSAME( UPLO, 'U' ) ) ) + $ THEN + INFO = -2 + ELSE IF( N.LT.0 ) THEN + INFO = -3 + ELSE IF( LDZ.LT.1 .OR. ( WANTZ .AND. LDZ.LT.N ) ) THEN + INFO = -7 + END IF +* + IF( INFO.EQ.0 ) THEN + IF( N.LE.1 ) THEN + LWMIN = 1 + LIWMIN = 1 + LRWMIN = 1 + ELSE + IF( WANTZ ) THEN + LWMIN = 2*N + LRWMIN = 1 + 5*N + 2*N**2 + LIWMIN = 3 + 5*N + ELSE + LWMIN = N + LRWMIN = N + LIWMIN = 1 + END IF + END IF + WORK( 1 ) = LWMIN + RWORK( 1 ) = LRWMIN + IWORK( 1 ) = LIWMIN +* + IF( LWORK.LT.LWMIN .AND. .NOT.LQUERY ) THEN + INFO = -9 + ELSE IF( LRWORK.LT.LRWMIN .AND. .NOT.LQUERY ) THEN + INFO = -11 + ELSE IF( LIWORK.LT.LIWMIN .AND. .NOT.LQUERY ) THEN + INFO = -13 + END IF + END IF +* + IF( INFO.NE.0 ) THEN + CALL XERBLA( 'CHPEVD', -INFO ) + RETURN + ELSE IF( LQUERY ) THEN + RETURN + END IF +* +* Quick return if possible +* + IF( N.EQ.0 ) + $ RETURN +* + IF( N.EQ.1 ) THEN + W( 1 ) = AP( 1 ) + IF( WANTZ ) + $ Z( 1, 1 ) = CONE + RETURN + END IF +* +* Get machine constants. +* + SAFMIN = SLAMCH( 'Safe minimum' ) + EPS = SLAMCH( 'Precision' ) + SMLNUM = SAFMIN / EPS + BIGNUM = ONE / SMLNUM + RMIN = SQRT( SMLNUM ) + RMAX = SQRT( BIGNUM ) +* +* Scale matrix to allowable range, if necessary. +* + ANRM = CLANHP( 'M', UPLO, N, AP, RWORK ) + ISCALE = 0 + IF( ANRM.GT.ZERO .AND. ANRM.LT.RMIN ) THEN + ISCALE = 1 + SIGMA = RMIN / ANRM + ELSE IF( ANRM.GT.RMAX ) THEN + ISCALE = 1 + SIGMA = RMAX / ANRM + END IF + IF( ISCALE.EQ.1 ) THEN + CALL CSSCAL( ( N*( N+1 ) ) / 2, SIGMA, AP, 1 ) + END IF +* +* Call CHPTRD to reduce Hermitian packed matrix to tridiagonal form. +* + INDE = 1 + INDTAU = 1 + INDRWK = INDE + N + INDWRK = INDTAU + N + LLWRK = LWORK - INDWRK + 1 + LLRWK = LRWORK - INDRWK + 1 + CALL CHPTRD( UPLO, N, AP, W, RWORK( INDE ), WORK( INDTAU ), + $ IINFO ) +* +* For eigenvalues only, call SSTERF. For eigenvectors, first call +* CUPGTR to generate the orthogonal matrix, then call CSTEDC. +* + IF( .NOT.WANTZ ) THEN + CALL SSTERF( N, W, RWORK( INDE ), INFO ) + ELSE + CALL CSTEDC( 'I', N, W, RWORK( INDE ), Z, LDZ, WORK( INDWRK ), + $ LLWRK, RWORK( INDRWK ), LLRWK, IWORK, LIWORK, + $ INFO ) + CALL CUPMTR( 'L', UPLO, 'N', N, N, AP, WORK( INDTAU ), Z, LDZ, + $ WORK( INDWRK ), IINFO ) + END IF +* +* If matrix was scaled, then rescale eigenvalues appropriately. +* + IF( ISCALE.EQ.1 ) THEN + IF( INFO.EQ.0 ) THEN + IMAX = N + ELSE + IMAX = INFO - 1 + END IF + CALL SSCAL( IMAX, ONE / SIGMA, W, 1 ) + END IF +* + WORK( 1 ) = LWMIN + RWORK( 1 ) = LRWMIN + IWORK( 1 ) = LIWMIN + RETURN +* +* End of CHPEVD +* + END |