OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
claghe.f
Go to the documentation of this file.
1 SUBROUTINE claghe( N, K, D, A, LDA, ISEED, WORK, INFO )
2*
3* -- LAPACK auxiliary test routine (version 3.1) --
4* Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
5* November 2006
6*
7* .. Scalar Arguments ..
8 INTEGER INFO, K, LDA, N
9* ..
10* .. Array Arguments ..
11 INTEGER ISEED( 4 )
12 REAL D( * )
13 COMPLEX A( LDA, * ), WORK( * )
14* ..
15*
16* Purpose
17* =======
18*
19* CLAGHE generates a complex hermitian matrix A, by pre- and post-
20* multiplying a real diagonal matrix D with a random unitary matrix:
21* A = U*D*U'. The semi-bandwidth may then be reduced to k by additional
22* unitary transformations.
23*
24* Arguments
25* =========
26*
27* N (input) INTEGER
28* The order of the matrix A. N >= 0.
29*
30* K (input) INTEGER
31* The number of nonzero subdiagonals within the band of A.
32* 0 <= K <= N-1.
33*
34* D (input) REAL array, dimension (N)
35* The diagonal elements of the diagonal matrix D.
36*
37* A (output) COMPLEX array, dimension (LDA,N)
38* The generated n by n hermitian matrix A (the full matrix is
39* stored).
40*
41* LDA (input) INTEGER
42* The leading dimension of the array A. LDA >= N.
43*
44* ISEED (input/output) INTEGER array, dimension (4)
45* On entry, the seed of the random number generator; the array
46* elements must be between 0 and 4095, and ISEED(4) must be
47* odd.
48* On exit, the seed is updated.
49*
50* WORK (workspace) COMPLEX array, dimension (2*N)
51*
52* INFO (output) INTEGER
53* = 0: successful exit
54* < 0: if INFO = -i, the i-th argument had an illegal value
55*
56* =====================================================================
57*
58* .. Parameters ..
59 COMPLEX ZERO, ONE, HALF
60 parameter( zero = ( 0.0e+0, 0.0e+0 ),
61 $ one = ( 1.0e+0, 0.0e+0 ),
62 $ half = ( 0.5e+0, 0.0e+0 ) )
63* ..
64* .. Local Scalars ..
65 INTEGER I, J
66 REAL WN
67 COMPLEX ALPHA, TAU, WA, WB
68* ..
69* .. External Subroutines ..
70 EXTERNAL caxpy, cgemv, cgerc, chemv, cher2, clarnv,
71 $ cscal, xerbla
72* ..
73* .. External Functions ..
74 REAL SCNRM2
75 COMPLEX CDOTC
76 EXTERNAL scnrm2, cdotc
77* ..
78* .. Intrinsic Functions ..
79 INTRINSIC abs, conjg, max, real
80* ..
81* .. Executable Statements ..
82*
83* Test the input arguments
84*
85 info = 0
86 IF( n.LT.0 ) THEN
87 info = -1
88 ELSE IF( k.LT.0 .OR. k.GT.n-1 ) THEN
89 info = -2
90 ELSE IF( lda.LT.max( 1, n ) ) THEN
91 info = -5
92 END IF
93 IF( info.LT.0 ) THEN
94 CALL xerbla( 'CLAGHE', -info )
95 RETURN
96 END IF
97*
98* initialize lower triangle of A to diagonal matrix
99*
100 DO 20 j = 1, n
101 DO 10 i = j + 1, n
102 a( i, j ) = zero
103 10 CONTINUE
104 20 CONTINUE
105 DO 30 i = 1, n
106 a( i, i ) = d( i )
107 30 CONTINUE
108*
109* Generate lower triangle of hermitian matrix
110*
111 DO 40 i = n - 1, 1, -1
112*
113* generate random reflection
114*
115 CALL clarnv( 3, iseed, n-i+1, work )
116 wn = scnrm2( n-i+1, work, 1 )
117 wa = ( wn / abs( work( 1 ) ) )*work( 1 )
118 IF( wn.EQ.zero ) THEN
119 tau = zero
120 ELSE
121 wb = work( 1 ) + wa
122 CALL cscal( n-i, one / wb, work( 2 ), 1 )
123 work( 1 ) = one
124 tau = real( wb / wa )
125 END IF
126*
127* apply random reflection to A(i:n,i:n) from the left
128* and the right
129*
130* compute y := tau * A * u
131*
132 CALL chemv( 'Lower', n-i+1, tau, a( i, i ), lda, work, 1, zero,
133 $ work( n+1 ), 1 )
134*
135* compute v := y - 1/2 * tau * ( y, u ) * u
136*
137 alpha = -half*tau*cdotc( n-i+1, work( n+1 ), 1, work, 1 )
138 CALL caxpy( n-i+1, alpha, work, 1, work( n+1 ), 1 )
139*
140* apply the transformation as a rank-2 update to A(i:n,i:n)
141*
142 CALL cher2( 'Lower', n-i+1, -one, work, 1, work( n+1 ), 1,
143 $ a( i, i ), lda )
144 40 CONTINUE
145*
146* Reduce number of subdiagonals to K
147*
148 DO 60 i = 1, n - 1 - k
149*
150* generate reflection to annihilate A(k+i+1:n,i)
151*
152 wn = scnrm2( n-k-i+1, a( k+i, i ), 1 )
153 wa = ( wn / abs( a( k+i, i ) ) )*a( k+i, i )
154 IF( wn.EQ.zero ) THEN
155 tau = zero
156 ELSE
157 wb = a( k+i, i ) + wa
158 CALL cscal( n-k-i, one / wb, a( k+i+1, i ), 1 )
159 a( k+i, i ) = one
160 tau = real( wb / wa )
161 END IF
162*
163* apply reflection to A(k+i:n,i+1:k+i-1) from the left
164*
165 CALL cgemv( 'Conjugate transpose', n-k-i+1, k-1, one,
166 $ a( k+i, i+1 ), lda, a( k+i, i ), 1, zero, work, 1 )
167 CALL cgerc( n-k-i+1, k-1, -tau, a( k+i, i ), 1, work, 1,
168 $ a( k+i, i+1 ), lda )
169*
170* apply reflection to A(k+i:n,k+i:n) from the left and the right
171*
172* compute y := tau * A * u
173*
174 CALL chemv( 'Lower', n-k-i+1, tau, a( k+i, k+i ), lda,
175 $ a( k+i, i ), 1, zero, work, 1 )
176*
177* compute v := y - 1/2 * tau * ( y, u ) * u
178*
179 alpha = -half*tau*cdotc( n-k-i+1, work, 1, a( k+i, i ), 1 )
180 CALL caxpy( n-k-i+1, alpha, a( k+i, i ), 1, work, 1 )
181*
182* apply hermitian rank-2 update to A(k+i:n,k+i:n)
183*
184 CALL cher2( 'Lower', n-k-i+1, -one, a( k+i, i ), 1, work, 1,
185 $ a( k+i, k+i ), lda )
186*
187 a( k+i, i ) = -wa
188 DO 50 j = k + i + 1, n
189 a( j, i ) = zero
190 50 CONTINUE
191 60 CONTINUE
192*
193* Store full hermitian matrix
194*
195 DO 80 j = 1, n
196 DO 70 i = j + 1, n
197 a( j, i ) = conjg( a( i, j ) )
198 70 CONTINUE
199 80 CONTINUE
200 RETURN
201*
202* End of CLAGHE
203*
204 END
subroutine xerbla(srname, info)
XERBLA
Definition xerbla.f:60
subroutine clarnv(idist, iseed, n, x)
CLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition clarnv.f:99
subroutine caxpy(n, ca, cx, incx, cy, incy)
CAXPY
Definition caxpy.f:88
subroutine cscal(n, ca, cx, incx)
CSCAL
Definition cscal.f:78
subroutine chemv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)
CHEMV
Definition chemv.f:154
subroutine cgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
CGEMV
Definition cgemv.f:158
subroutine cgerc(m, n, alpha, x, incx, y, incy, a, lda)
CGERC
Definition cgerc.f:130
subroutine cher2(uplo, n, alpha, x, incx, y, incy, a, lda)
CHER2
Definition cher2.f:150
#define max(a, b)
Definition macros.h:21
subroutine claghe(n, k, d, a, lda, iseed, work, info)
Definition claghe.f:2