summaryrefslogtreecommitdiff
path: root/2.3-1/src/fortran/lapack/zhetd2.f
diff options
context:
space:
mode:
Diffstat (limited to '2.3-1/src/fortran/lapack/zhetd2.f')
-rw-r--r--2.3-1/src/fortran/lapack/zhetd2.f258
1 files changed, 258 insertions, 0 deletions
diff --git a/2.3-1/src/fortran/lapack/zhetd2.f b/2.3-1/src/fortran/lapack/zhetd2.f
new file mode 100644
index 00000000..24b0a1df
--- /dev/null
+++ b/2.3-1/src/fortran/lapack/zhetd2.f
@@ -0,0 +1,258 @@
+ SUBROUTINE ZHETD2( UPLO, N, A, LDA, D, E, TAU, INFO )
+*
+* -- LAPACK routine (version 3.1) --
+* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
+* November 2006
+*
+* .. Scalar Arguments ..
+ CHARACTER UPLO
+ INTEGER INFO, LDA, N
+* ..
+* .. Array Arguments ..
+ DOUBLE PRECISION D( * ), E( * )
+ COMPLEX*16 A( LDA, * ), TAU( * )
+* ..
+*
+* Purpose
+* =======
+*
+* ZHETD2 reduces a complex Hermitian matrix A to real symmetric
+* tridiagonal form T by a unitary similarity transformation:
+* Q' * A * Q = T.
+*
+* Arguments
+* =========
+*
+* UPLO (input) CHARACTER*1
+* Specifies whether the upper or lower triangular part of the
+* Hermitian matrix A is stored:
+* = 'U': Upper triangular
+* = 'L': Lower triangular
+*
+* N (input) INTEGER
+* The order of the matrix A. N >= 0.
+*
+* A (input/output) COMPLEX*16 array, dimension (LDA,N)
+* On entry, the Hermitian matrix A. If UPLO = 'U', the leading
+* n-by-n upper triangular part of A contains the upper
+* triangular part of the matrix A, and the strictly lower
+* triangular part of A is not referenced. If UPLO = 'L', the
+* leading n-by-n lower triangular part of A contains the lower
+* triangular part of the matrix A, and the strictly upper
+* triangular part of A is not referenced.
+* On exit, if UPLO = 'U', the diagonal and first superdiagonal
+* of A are overwritten by the corresponding elements of the
+* tridiagonal matrix T, and the elements above the first
+* superdiagonal, with the array TAU, represent the unitary
+* matrix Q as a product of elementary reflectors; if UPLO
+* = 'L', the diagonal and first subdiagonal of A are over-
+* written by the corresponding elements of the tridiagonal
+* matrix T, and the elements below the first subdiagonal, with
+* the array TAU, represent the unitary matrix Q as a product
+* of elementary reflectors. See Further Details.
+*
+* LDA (input) INTEGER
+* The leading dimension of the array A. LDA >= max(1,N).
+*
+* D (output) DOUBLE PRECISION array, dimension (N)
+* The diagonal elements of the tridiagonal matrix T:
+* D(i) = A(i,i).
+*
+* E (output) DOUBLE PRECISION array, dimension (N-1)
+* The off-diagonal elements of the tridiagonal matrix T:
+* E(i) = A(i,i+1) if UPLO = 'U', E(i) = A(i+1,i) if UPLO = 'L'.
+*
+* TAU (output) COMPLEX*16 array, dimension (N-1)
+* The scalar factors of the elementary reflectors (see Further
+* Details).
+*
+* INFO (output) INTEGER
+* = 0: successful exit
+* < 0: if INFO = -i, the i-th argument had an illegal value.
+*
+* Further Details
+* ===============
+*
+* If UPLO = 'U', the matrix Q is represented as a product of elementary
+* reflectors
+*
+* Q = H(n-1) . . . H(2) H(1).
+*
+* Each H(i) has the form
+*
+* H(i) = I - tau * v * v'
+*
+* where tau is a complex scalar, and v is a complex vector with
+* v(i+1:n) = 0 and v(i) = 1; v(1:i-1) is stored on exit in
+* A(1:i-1,i+1), and tau in TAU(i).
+*
+* If UPLO = 'L', the matrix Q is represented as a product of elementary
+* reflectors
+*
+* Q = H(1) H(2) . . . H(n-1).
+*
+* Each H(i) has the form
+*
+* H(i) = I - tau * v * v'
+*
+* where tau is a complex scalar, and v is a complex vector with
+* v(1:i) = 0 and v(i+1) = 1; v(i+2:n) is stored on exit in A(i+2:n,i),
+* and tau in TAU(i).
+*
+* The contents of A on exit are illustrated by the following examples
+* with n = 5:
+*
+* if UPLO = 'U': if UPLO = 'L':
+*
+* ( d e v2 v3 v4 ) ( d )
+* ( d e v3 v4 ) ( e d )
+* ( d e v4 ) ( v1 e d )
+* ( d e ) ( v1 v2 e d )
+* ( d ) ( v1 v2 v3 e d )
+*
+* where d and e denote diagonal and off-diagonal elements of T, and vi
+* denotes an element of the vector defining H(i).
+*
+* =====================================================================
+*
+* .. Parameters ..
+ COMPLEX*16 ONE, ZERO, HALF
+ PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ),
+ $ ZERO = ( 0.0D+0, 0.0D+0 ),
+ $ HALF = ( 0.5D+0, 0.0D+0 ) )
+* ..
+* .. Local Scalars ..
+ LOGICAL UPPER
+ INTEGER I
+ COMPLEX*16 ALPHA, TAUI
+* ..
+* .. External Subroutines ..
+ EXTERNAL XERBLA, ZAXPY, ZHEMV, ZHER2, ZLARFG
+* ..
+* .. External Functions ..
+ LOGICAL LSAME
+ COMPLEX*16 ZDOTC
+ EXTERNAL LSAME, ZDOTC
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC DBLE, MAX, MIN
+* ..
+* .. Executable Statements ..
+*
+* Test the input parameters
+*
+ INFO = 0
+ UPPER = LSAME( UPLO, 'U' )
+ IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
+ INFO = -1
+ ELSE IF( N.LT.0 ) THEN
+ INFO = -2
+ ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
+ INFO = -4
+ END IF
+ IF( INFO.NE.0 ) THEN
+ CALL XERBLA( 'ZHETD2', -INFO )
+ RETURN
+ END IF
+*
+* Quick return if possible
+*
+ IF( N.LE.0 )
+ $ RETURN
+*
+ IF( UPPER ) THEN
+*
+* Reduce the upper triangle of A
+*
+ A( N, N ) = DBLE( A( N, N ) )
+ DO 10 I = N - 1, 1, -1
+*
+* Generate elementary reflector H(i) = I - tau * v * v'
+* to annihilate A(1:i-1,i+1)
+*
+ ALPHA = A( I, I+1 )
+ CALL ZLARFG( I, ALPHA, A( 1, I+1 ), 1, TAUI )
+ E( I ) = ALPHA
+*
+ IF( TAUI.NE.ZERO ) THEN
+*
+* Apply H(i) from both sides to A(1:i,1:i)
+*
+ A( I, I+1 ) = ONE
+*
+* Compute x := tau * A * v storing x in TAU(1:i)
+*
+ CALL ZHEMV( UPLO, I, TAUI, A, LDA, A( 1, I+1 ), 1, ZERO,
+ $ TAU, 1 )
+*
+* Compute w := x - 1/2 * tau * (x'*v) * v
+*
+ ALPHA = -HALF*TAUI*ZDOTC( I, TAU, 1, A( 1, I+1 ), 1 )
+ CALL ZAXPY( I, ALPHA, A( 1, I+1 ), 1, TAU, 1 )
+*
+* Apply the transformation as a rank-2 update:
+* A := A - v * w' - w * v'
+*
+ CALL ZHER2( UPLO, I, -ONE, A( 1, I+1 ), 1, TAU, 1, A,
+ $ LDA )
+*
+ ELSE
+ A( I, I ) = DBLE( A( I, I ) )
+ END IF
+ A( I, I+1 ) = E( I )
+ D( I+1 ) = A( I+1, I+1 )
+ TAU( I ) = TAUI
+ 10 CONTINUE
+ D( 1 ) = A( 1, 1 )
+ ELSE
+*
+* Reduce the lower triangle of A
+*
+ A( 1, 1 ) = DBLE( A( 1, 1 ) )
+ DO 20 I = 1, N - 1
+*
+* Generate elementary reflector H(i) = I - tau * v * v'
+* to annihilate A(i+2:n,i)
+*
+ ALPHA = A( I+1, I )
+ CALL ZLARFG( N-I, ALPHA, A( MIN( I+2, N ), I ), 1, TAUI )
+ E( I ) = ALPHA
+*
+ IF( TAUI.NE.ZERO ) THEN
+*
+* Apply H(i) from both sides to A(i+1:n,i+1:n)
+*
+ A( I+1, I ) = ONE
+*
+* Compute x := tau * A * v storing y in TAU(i:n-1)
+*
+ CALL ZHEMV( UPLO, N-I, TAUI, A( I+1, I+1 ), LDA,
+ $ A( I+1, I ), 1, ZERO, TAU( I ), 1 )
+*
+* Compute w := x - 1/2 * tau * (x'*v) * v
+*
+ ALPHA = -HALF*TAUI*ZDOTC( N-I, TAU( I ), 1, A( I+1, I ),
+ $ 1 )
+ CALL ZAXPY( N-I, ALPHA, A( I+1, I ), 1, TAU( I ), 1 )
+*
+* Apply the transformation as a rank-2 update:
+* A := A - v * w' - w * v'
+*
+ CALL ZHER2( UPLO, N-I, -ONE, A( I+1, I ), 1, TAU( I ), 1,
+ $ A( I+1, I+1 ), LDA )
+*
+ ELSE
+ A( I+1, I+1 ) = DBLE( A( I+1, I+1 ) )
+ END IF
+ A( I+1, I ) = E( I )
+ D( I ) = A( I, I )
+ TAU( I ) = TAUI
+ 20 CONTINUE
+ D( N ) = A( N, N )
+ END IF
+*
+ RETURN
+*
+* End of ZHETD2
+*
+ END