annotate libcruft/lapack/zhetrd.f @ 5086:55f5b61d74b7

[project @ 2004-11-19 21:50:50 by jwe]
author jwe
date Fri, 19 Nov 2004 21:50:50 +0000
parents 15cddaacbc2d
children 68db500cb558
Ignore whitespace changes - Everywhere: Within whitespace: At end of lines:
rev   line source
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
1 SUBROUTINE ZHETRD( UPLO, N, A, LDA, D, E, TAU, WORK, LWORK, INFO )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
2 *
3333
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
3 * -- LAPACK routine (version 3.0) --
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
4 * Univ. of Tennessee, Univ. of California Berkeley, NAG Ltd.,
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
5 * Courant Institute, Argonne National Lab, and Rice University
3333
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
6 * June 30, 1999
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
7 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
8 * .. Scalar Arguments ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
9 CHARACTER UPLO
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
10 INTEGER INFO, LDA, LWORK, N
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
11 * ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
12 * .. Array Arguments ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
13 DOUBLE PRECISION D( * ), E( * )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
14 COMPLEX*16 A( LDA, * ), TAU( * ), WORK( * )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
15 * ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
16 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
17 * Purpose
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
18 * =======
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
19 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
20 * ZHETRD reduces a complex Hermitian matrix A to real symmetric
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
21 * tridiagonal form T by a unitary similarity transformation:
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
22 * Q**H * A * Q = T.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
23 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
24 * Arguments
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
25 * =========
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
26 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
27 * UPLO (input) CHARACTER*1
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
28 * = 'U': Upper triangle of A is stored;
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
29 * = 'L': Lower triangle of A is stored.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
30 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
31 * N (input) INTEGER
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
32 * The order of the matrix A. N >= 0.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
33 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
34 * A (input/output) COMPLEX*16 array, dimension (LDA,N)
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
35 * On entry, the Hermitian matrix A. If UPLO = 'U', the leading
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
36 * N-by-N upper triangular part of A contains the upper
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
37 * triangular part of the matrix A, and the strictly lower
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
38 * triangular part of A is not referenced. If UPLO = 'L', the
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
39 * leading N-by-N lower triangular part of A contains the lower
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
40 * triangular part of the matrix A, and the strictly upper
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
41 * triangular part of A is not referenced.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
42 * On exit, if UPLO = 'U', the diagonal and first superdiagonal
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
43 * of A are overwritten by the corresponding elements of the
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
44 * tridiagonal matrix T, and the elements above the first
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
45 * superdiagonal, with the array TAU, represent the unitary
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
46 * matrix Q as a product of elementary reflectors; if UPLO
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
47 * = 'L', the diagonal and first subdiagonal of A are over-
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
48 * written by the corresponding elements of the tridiagonal
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
49 * matrix T, and the elements below the first subdiagonal, with
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
50 * the array TAU, represent the unitary matrix Q as a product
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
51 * of elementary reflectors. See Further Details.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
52 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
53 * LDA (input) INTEGER
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
54 * The leading dimension of the array A. LDA >= max(1,N).
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
55 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
56 * D (output) DOUBLE PRECISION array, dimension (N)
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
57 * The diagonal elements of the tridiagonal matrix T:
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
58 * D(i) = A(i,i).
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
59 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
60 * E (output) DOUBLE PRECISION array, dimension (N-1)
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
61 * The off-diagonal elements of the tridiagonal matrix T:
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
62 * E(i) = A(i,i+1) if UPLO = 'U', E(i) = A(i+1,i) if UPLO = 'L'.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
63 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
64 * TAU (output) COMPLEX*16 array, dimension (N-1)
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
65 * The scalar factors of the elementary reflectors (see Further
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
66 * Details).
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
67 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
68 * WORK (workspace/output) COMPLEX*16 array, dimension (LWORK)
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
69 * On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
70 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
71 * LWORK (input) INTEGER
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
72 * The dimension of the array WORK. LWORK >= 1.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
73 * For optimum performance LWORK >= N*NB, where NB is the
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
74 * optimal blocksize.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
75 *
3333
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
76 * If LWORK = -1, then a workspace query is assumed; the routine
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
77 * only calculates the optimal size of the WORK array, returns
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
78 * this value as the first entry of the WORK array, and no error
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
79 * message related to LWORK is issued by XERBLA.
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
80 *
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
81 * INFO (output) INTEGER
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
82 * = 0: successful exit
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
83 * < 0: if INFO = -i, the i-th argument had an illegal value
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
84 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
85 * Further Details
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
86 * ===============
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
87 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
88 * If UPLO = 'U', the matrix Q is represented as a product of elementary
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
89 * reflectors
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
90 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
91 * Q = H(n-1) . . . H(2) H(1).
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
92 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
93 * Each H(i) has the form
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
94 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
95 * H(i) = I - tau * v * v'
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
96 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
97 * where tau is a complex scalar, and v is a complex vector with
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
98 * v(i+1:n) = 0 and v(i) = 1; v(1:i-1) is stored on exit in
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
99 * A(1:i-1,i+1), and tau in TAU(i).
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
100 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
101 * If UPLO = 'L', the matrix Q is represented as a product of elementary
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
102 * reflectors
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
103 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
104 * Q = H(1) H(2) . . . H(n-1).
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
105 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
106 * Each H(i) has the form
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
107 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
108 * H(i) = I - tau * v * v'
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
109 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
110 * where tau is a complex scalar, and v is a complex vector with
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
111 * v(1:i) = 0 and v(i+1) = 1; v(i+2:n) is stored on exit in A(i+2:n,i),
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
112 * and tau in TAU(i).
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
113 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
114 * The contents of A on exit are illustrated by the following examples
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
115 * with n = 5:
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
116 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
117 * if UPLO = 'U': if UPLO = 'L':
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
118 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
119 * ( d e v2 v3 v4 ) ( d )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
120 * ( d e v3 v4 ) ( e d )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
121 * ( d e v4 ) ( v1 e d )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
122 * ( d e ) ( v1 v2 e d )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
123 * ( d ) ( v1 v2 v3 e d )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
124 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
125 * where d and e denote diagonal and off-diagonal elements of T, and vi
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
126 * denotes an element of the vector defining H(i).
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
127 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
128 * =====================================================================
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
129 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
130 * .. Parameters ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
131 DOUBLE PRECISION ONE
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
132 PARAMETER ( ONE = 1.0D+0 )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
133 COMPLEX*16 CONE
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
134 PARAMETER ( CONE = ( 1.0D+0, 0.0D+0 ) )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
135 * ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
136 * .. Local Scalars ..
3333
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
137 LOGICAL LQUERY, UPPER
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
138 INTEGER I, IINFO, IWS, J, KK, LDWORK, LWKOPT, NB,
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
139 $ NBMIN, NX
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
140 * ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
141 * .. External Subroutines ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
142 EXTERNAL XERBLA, ZHER2K, ZHETD2, ZLATRD
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
143 * ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
144 * .. Intrinsic Functions ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
145 INTRINSIC MAX
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
146 * ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
147 * .. External Functions ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
148 LOGICAL LSAME
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
149 INTEGER ILAENV
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
150 EXTERNAL LSAME, ILAENV
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
151 * ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
152 * .. Executable Statements ..
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
153 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
154 * Test the input parameters
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
155 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
156 INFO = 0
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
157 UPPER = LSAME( UPLO, 'U' )
3333
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
158 LQUERY = ( LWORK.EQ.-1 )
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
159 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
160 INFO = -1
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
161 ELSE IF( N.LT.0 ) THEN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
162 INFO = -2
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
163 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
164 INFO = -4
3333
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
165 ELSE IF( LWORK.LT.1 .AND. .NOT.LQUERY ) THEN
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
166 INFO = -9
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
167 END IF
3333
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
168 *
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
169 IF( INFO.EQ.0 ) THEN
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
170 *
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
171 * Determine the block size.
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
172 *
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
173 NB = ILAENV( 1, 'ZHETRD', UPLO, N, -1, -1, -1 )
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
174 LWKOPT = N*NB
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
175 WORK( 1 ) = LWKOPT
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
176 END IF
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
177 *
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
178 IF( INFO.NE.0 ) THEN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
179 CALL XERBLA( 'ZHETRD', -INFO )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
180 RETURN
3333
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
181 ELSE IF( LQUERY ) THEN
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
182 RETURN
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
183 END IF
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
184 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
185 * Quick return if possible
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
186 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
187 IF( N.EQ.0 ) THEN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
188 WORK( 1 ) = 1
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
189 RETURN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
190 END IF
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
191 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
192 NX = N
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
193 IWS = 1
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
194 IF( NB.GT.1 .AND. NB.LT.N ) THEN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
195 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
196 * Determine when to cross over from blocked to unblocked code
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
197 * (last block is always handled by unblocked code).
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
198 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
199 NX = MAX( NB, ILAENV( 3, 'ZHETRD', UPLO, N, -1, -1, -1 ) )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
200 IF( NX.LT.N ) THEN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
201 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
202 * Determine if workspace is large enough for blocked code.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
203 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
204 LDWORK = N
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
205 IWS = LDWORK*NB
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
206 IF( LWORK.LT.IWS ) THEN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
207 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
208 * Not enough workspace to use optimal NB: determine the
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
209 * minimum value of NB, and reduce NB or force use of
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
210 * unblocked code by setting NX = N.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
211 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
212 NB = MAX( LWORK / LDWORK, 1 )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
213 NBMIN = ILAENV( 2, 'ZHETRD', UPLO, N, -1, -1, -1 )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
214 IF( NB.LT.NBMIN )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
215 $ NX = N
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
216 END IF
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
217 ELSE
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
218 NX = N
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
219 END IF
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
220 ELSE
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
221 NB = 1
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
222 END IF
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
223 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
224 IF( UPPER ) THEN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
225 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
226 * Reduce the upper triangle of A.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
227 * Columns 1:kk are handled by the unblocked method.
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
228 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
229 KK = N - ( ( N-NX+NB-1 ) / NB )*NB
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
230 DO 20 I = N - NB + 1, KK + 1, -NB
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
231 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
232 * Reduce columns i:i+nb-1 to tridiagonal form and form the
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
233 * matrix W which is needed to update the unreduced part of
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
234 * the matrix
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
235 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
236 CALL ZLATRD( UPLO, I+NB-1, NB, A, LDA, E, TAU, WORK,
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
237 $ LDWORK )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
238 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
239 * Update the unreduced submatrix A(1:i-1,1:i-1), using an
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
240 * update of the form: A := A - V*W' - W*V'
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
241 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
242 CALL ZHER2K( UPLO, 'No transpose', I-1, NB, -CONE,
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
243 $ A( 1, I ), LDA, WORK, LDWORK, ONE, A, LDA )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
244 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
245 * Copy superdiagonal elements back into A, and diagonal
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
246 * elements into D
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
247 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
248 DO 10 J = I, I + NB - 1
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
249 A( J-1, J ) = E( J-1 )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
250 D( J ) = A( J, J )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
251 10 CONTINUE
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
252 20 CONTINUE
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
253 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
254 * Use unblocked code to reduce the last or only block
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
255 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
256 CALL ZHETD2( UPLO, KK, A, LDA, D, E, TAU, IINFO )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
257 ELSE
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
258 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
259 * Reduce the lower triangle of A
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
260 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
261 DO 40 I = 1, N - NX, NB
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
262 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
263 * Reduce columns i:i+nb-1 to tridiagonal form and form the
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
264 * matrix W which is needed to update the unreduced part of
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
265 * the matrix
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
266 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
267 CALL ZLATRD( UPLO, N-I+1, NB, A( I, I ), LDA, E( I ),
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
268 $ TAU( I ), WORK, LDWORK )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
269 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
270 * Update the unreduced submatrix A(i+nb:n,i+nb:n), using
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
271 * an update of the form: A := A - V*W' - W*V'
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
272 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
273 CALL ZHER2K( UPLO, 'No transpose', N-I-NB+1, NB, -CONE,
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
274 $ A( I+NB, I ), LDA, WORK( NB+1 ), LDWORK, ONE,
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
275 $ A( I+NB, I+NB ), LDA )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
276 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
277 * Copy subdiagonal elements back into A, and diagonal
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
278 * elements into D
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
279 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
280 DO 30 J = I, I + NB - 1
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
281 A( J+1, J ) = E( J )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
282 D( J ) = A( J, J )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
283 30 CONTINUE
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
284 40 CONTINUE
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
285 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
286 * Use unblocked code to reduce the last or only block
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
287 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
288 CALL ZHETD2( UPLO, N-I+1, A( I, I ), LDA, D( I ), E( I ),
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
289 $ TAU( I ), IINFO )
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
290 END IF
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
291 *
3333
15cddaacbc2d [project @ 1999-11-03 19:53:59 by jwe]
jwe
parents: 2814
diff changeset
292 WORK( 1 ) = LWKOPT
2814
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
293 RETURN
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
294 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
295 * End of ZHETRD
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
296 *
ffa60dc8e49b [project @ 1997-03-14 04:30:59 by jwe]
jwe
parents:
diff changeset
297 END