OpenRadioss 2025.1.11
OpenRadioss project
Loading...
Searching...
No Matches
zlagsy.f
Go to the documentation of this file.
1 SUBROUTINE zlagsy( 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 DOUBLE PRECISION D( * )
13 COMPLEX*16 A( LDA, * ), WORK( * )
14* ..
15*
16* Purpose
17* =======
18*
19* ZLAGSY generates a complex symmetric matrix A, by pre- and post-
20* multiplying a real diagonal matrix D with a random unitary matrix:
21* A = U*D*U**T. The semi-bandwidth may then be reduced to k by
22* additional 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) DOUBLE PRECISION array, dimension (N)
35* The diagonal elements of the diagonal matrix D.
36*
37* A (output) COMPLEX*16 array, dimension (LDA,N)
38* The generated n by n symmetric 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*16 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*16 ZERO, ONE, HALF
60 parameter( zero = ( 0.0d+0, 0.0d+0 ),
61 $ one = ( 1.0d+0, 0.0d+0 ),
62 $ half = ( 0.5d+0, 0.0d+0 ) )
63* ..
64* .. Local Scalars ..
65 INTEGER I, II, J, JJ
66 DOUBLE PRECISION WN
67 COMPLEX*16 ALPHA, TAU, WA, WB
68* ..
69* .. External Subroutines ..
70 EXTERNAL xerbla, zaxpy, zgemv, zgerc, zlacgv, zlarnv,
71 $ zscal, zsymv
72* ..
73* .. External Functions ..
74 DOUBLE PRECISION DZNRM2
75 COMPLEX*16 ZDOTC
76 EXTERNAL dznrm2, zdotc
77* ..
78* .. Intrinsic Functions ..
79 INTRINSIC abs, dble, max
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( 'ZLAGSY', -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 symmetric matrix
110*
111 DO 60 i = n - 1, 1, -1
112*
113* generate random reflection
114*
115 CALL zlarnv( 3, iseed, n-i+1, work )
116 wn = dznrm2( 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 zscal( n-i, one / wb, work( 2 ), 1 )
123 work( 1 ) = one
124 tau = dble( 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 * conjg(u)
131*
132 CALL zlacgv( n-i+1, work, 1 )
133 CALL zsymv( 'Lower', n-i+1, tau, a( i, i ), lda, work, 1, zero,
134 $ work( n+1 ), 1 )
135 CALL zlacgv( n-i+1, work, 1 )
136*
137* compute v := y - 1/2 * tau * ( u, y ) * u
138*
139 alpha = -half*tau*zdotc( n-i+1, work, 1, work( n+1 ), 1 )
140 CALL zaxpy( n-i+1, alpha, work, 1, work( n+1 ), 1 )
141*
142* apply the transformation as a rank-2 update to A(i:n,i:n)
143*
144* CALL ZSYR2( 'Lower', N-I+1, -ONE, WORK, 1, WORK( N+1 ), 1,
145* $ A( I, I ), LDA )
146*
147 DO 50 jj = i, n
148 DO 40 ii = jj, n
149 a( ii, jj ) = a( ii, jj ) -
150 $ work( ii-i+1 )*work( n+jj-i+1 ) -
151 $ work( n+ii-i+1 )*work( jj-i+1 )
152 40 CONTINUE
153 50 CONTINUE
154 60 CONTINUE
155*
156* Reduce number of subdiagonals to K
157*
158 DO 100 i = 1, n - 1 - k
159*
160* generate reflection to annihilate A(k+i+1:n,i)
161*
162 wn = dznrm2( n-k-i+1, a( k+i, i ), 1 )
163 wa = ( wn / abs( a( k+i, i ) ) )*a( k+i, i )
164 IF( wn.EQ.zero ) THEN
165 tau = zero
166 ELSE
167 wb = a( k+i, i ) + wa
168 CALL zscal( n-k-i, one / wb, a( k+i+1, i ), 1 )
169 a( k+i, i ) = one
170 tau = dble( wb / wa )
171 END IF
172*
173* apply reflection to A(k+i:n,i+1:k+i-1) from the left
174*
175 CALL zgemv( 'Conjugate transpose', n-k-i+1, k-1, one,
176 $ a( k+i, i+1 ), lda, a( k+i, i ), 1, zero, work, 1 )
177 CALL zgerc( n-k-i+1, k-1, -tau, a( k+i, i ), 1, work, 1,
178 $ a( k+i, i+1 ), lda )
179*
180* apply reflection to A(k+i:n,k+i:n) from the left and the right
181*
182* compute y := tau * A * conjg(u)
183*
184 CALL zlacgv( n-k-i+1, a( k+i, i ), 1 )
185 CALL zsymv( 'Lower', n-k-i+1, tau, a( k+i, k+i ), lda,
186 $ a( k+i, i ), 1, zero, work, 1 )
187 CALL zlacgv( n-k-i+1, a( k+i, i ), 1 )
188*
189* compute v := y - 1/2 * tau * ( u, y ) * u
190*
191 alpha = -half*tau*zdotc( n-k-i+1, a( k+i, i ), 1, work, 1 )
192 CALL zaxpy( n-k-i+1, alpha, a( k+i, i ), 1, work, 1 )
193*
194* apply symmetric rank-2 update to A(k+i:n,k+i:n)
195*
196* CALL ZSYR2( 'Lower', N-K-I+1, -ONE, A( K+I, I ), 1, WORK, 1,
197* $ A( K+I, K+I ), LDA )
198*
199 DO 80 jj = k + i, n
200 DO 70 ii = jj, n
201 a( ii, jj ) = a( ii, jj ) - a( ii, i )*work( jj-k-i+1 ) -
202 $ work( ii-k-i+1 )*a( jj, i )
203 70 CONTINUE
204 80 CONTINUE
205*
206 a( k+i, i ) = -wa
207 DO 90 j = k + i + 1, n
208 a( j, i ) = zero
209 90 CONTINUE
210 100 CONTINUE
211*
212* Store full symmetric matrix
213*
214 DO 120 j = 1, n
215 DO 110 i = j + 1, n
216 a( j, i ) = a( i, j )
217 110 CONTINUE
218 120 CONTINUE
219 RETURN
220*
221* End of ZLAGSY
222*
223 END
#define alpha
Definition eval.h:35
subroutine xerbla(srname, info)
XERBLA
Definition xerbla.f:60
subroutine zlarnv(idist, iseed, n, x)
ZLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition zlarnv.f:99
subroutine zlacgv(n, x, incx)
ZLACGV conjugates a complex vector.
Definition zlacgv.f:74
subroutine zsymv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)
ZSYMV computes a matrix-vector product for a complex symmetric matrix.
Definition zsymv.f:157
subroutine zaxpy(n, za, zx, incx, zy, incy)
ZAXPY
Definition zaxpy.f:88
subroutine zscal(n, za, zx, incx)
ZSCAL
Definition zscal.f:78
subroutine zgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
ZGEMV
Definition zgemv.f:158
subroutine zgerc(m, n, alpha, x, incx, y, incy, a, lda)
ZGERC
Definition zgerc.f:130
#define max(a, b)
Definition macros.h:21
subroutine zlagsy(n, k, d, a, lda, iseed, work, info)
Definition zlagsy.f:2