LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
slagsy.f
Go to the documentation of this file.
1 *> \brief \b SLAGSY
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE SLAGSY( N, K, D, A, LDA, ISEED, WORK, INFO )
12 *
13 * .. Scalar Arguments ..
14 * INTEGER INFO, K, LDA, N
15 * ..
16 * .. Array Arguments ..
17 * INTEGER ISEED( 4 )
18 * REAL A( LDA, * ), D( * ), WORK( * )
19 * ..
20 *
21 *
22 *> \par Purpose:
23 * =============
24 *>
25 *> \verbatim
26 *>
27 *> SLAGSY generates a real symmetric matrix A, by pre- and post-
28 *> multiplying a real diagonal matrix D with a random orthogonal matrix:
29 *> A = U*D*U'. The semi-bandwidth may then be reduced to k by additional
30 *> orthogonal transformations.
31 *> \endverbatim
32 *
33 * Arguments:
34 * ==========
35 *
36 *> \param[in] N
37 *> \verbatim
38 *> N is INTEGER
39 *> The order of the matrix A. N >= 0.
40 *> \endverbatim
41 *>
42 *> \param[in] K
43 *> \verbatim
44 *> K is INTEGER
45 *> The number of nonzero subdiagonals within the band of A.
46 *> 0 <= K <= N-1.
47 *> \endverbatim
48 *>
49 *> \param[in] D
50 *> \verbatim
51 *> D is REAL array, dimension (N)
52 *> The diagonal elements of the diagonal matrix D.
53 *> \endverbatim
54 *>
55 *> \param[out] A
56 *> \verbatim
57 *> A is REAL array, dimension (LDA,N)
58 *> The generated n by n symmetric matrix A (the full matrix is
59 *> stored).
60 *> \endverbatim
61 *>
62 *> \param[in] LDA
63 *> \verbatim
64 *> LDA is INTEGER
65 *> The leading dimension of the array A. LDA >= N.
66 *> \endverbatim
67 *>
68 *> \param[in,out] ISEED
69 *> \verbatim
70 *> ISEED is INTEGER array, dimension (4)
71 *> On entry, the seed of the random number generator; the array
72 *> elements must be between 0 and 4095, and ISEED(4) must be
73 *> odd.
74 *> On exit, the seed is updated.
75 *> \endverbatim
76 *>
77 *> \param[out] WORK
78 *> \verbatim
79 *> WORK is REAL array, dimension (2*N)
80 *> \endverbatim
81 *>
82 *> \param[out] INFO
83 *> \verbatim
84 *> INFO is INTEGER
85 *> = 0: successful exit
86 *> < 0: if INFO = -i, the i-th argument had an illegal value
87 *> \endverbatim
88 *
89 * Authors:
90 * ========
91 *
92 *> \author Univ. of Tennessee
93 *> \author Univ. of California Berkeley
94 *> \author Univ. of Colorado Denver
95 *> \author NAG Ltd.
96 *
97 *> \date November 2011
98 *
99 *> \ingroup real_matgen
100 *
101 * =====================================================================
102  SUBROUTINE slagsy( N, K, D, A, LDA, ISEED, WORK, INFO )
103 *
104 * -- LAPACK auxiliary routine (version 3.4.0) --
105 * -- LAPACK is a software package provided by Univ. of Tennessee, --
106 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
107 * November 2011
108 *
109 * .. Scalar Arguments ..
110  INTEGER INFO, K, LDA, N
111 * ..
112 * .. Array Arguments ..
113  INTEGER ISEED( 4 )
114  REAL A( lda, * ), D( * ), WORK( * )
115 * ..
116 *
117 * =====================================================================
118 *
119 * .. Parameters ..
120  REAL ZERO, ONE, HALF
121  parameter ( zero = 0.0e+0, one = 1.0e+0, half = 0.5e+0 )
122 * ..
123 * .. Local Scalars ..
124  INTEGER I, J
125  REAL ALPHA, TAU, WA, WB, WN
126 * ..
127 * .. External Subroutines ..
128  EXTERNAL saxpy, sgemv, sger, slarnv, sscal, ssymv,
129  $ ssyr2, xerbla
130 * ..
131 * .. External Functions ..
132  REAL SDOT, SNRM2
133  EXTERNAL sdot, snrm2
134 * ..
135 * .. Intrinsic Functions ..
136  INTRINSIC max, sign
137 * ..
138 * .. Executable Statements ..
139 *
140 * Test the input arguments
141 *
142  info = 0
143  IF( n.LT.0 ) THEN
144  info = -1
145  ELSE IF( k.LT.0 .OR. k.GT.n-1 ) THEN
146  info = -2
147  ELSE IF( lda.LT.max( 1, n ) ) THEN
148  info = -5
149  END IF
150  IF( info.LT.0 ) THEN
151  CALL xerbla( 'SLAGSY', -info )
152  RETURN
153  END IF
154 *
155 * initialize lower triangle of A to diagonal matrix
156 *
157  DO 20 j = 1, n
158  DO 10 i = j + 1, n
159  a( i, j ) = zero
160  10 CONTINUE
161  20 CONTINUE
162  DO 30 i = 1, n
163  a( i, i ) = d( i )
164  30 CONTINUE
165 *
166 * Generate lower triangle of symmetric matrix
167 *
168  DO 40 i = n - 1, 1, -1
169 *
170 * generate random reflection
171 *
172  CALL slarnv( 3, iseed, n-i+1, work )
173  wn = snrm2( n-i+1, work, 1 )
174  wa = sign( wn, work( 1 ) )
175  IF( wn.EQ.zero ) THEN
176  tau = zero
177  ELSE
178  wb = work( 1 ) + wa
179  CALL sscal( n-i, one / wb, work( 2 ), 1 )
180  work( 1 ) = one
181  tau = wb / wa
182  END IF
183 *
184 * apply random reflection to A(i:n,i:n) from the left
185 * and the right
186 *
187 * compute y := tau * A * u
188 *
189  CALL ssymv( 'Lower', n-i+1, tau, a( i, i ), lda, work, 1, zero,
190  $ work( n+1 ), 1 )
191 *
192 * compute v := y - 1/2 * tau * ( y, u ) * u
193 *
194  alpha = -half*tau*sdot( n-i+1, work( n+1 ), 1, work, 1 )
195  CALL saxpy( n-i+1, alpha, work, 1, work( n+1 ), 1 )
196 *
197 * apply the transformation as a rank-2 update to A(i:n,i:n)
198 *
199  CALL ssyr2( 'Lower', n-i+1, -one, work, 1, work( n+1 ), 1,
200  $ a( i, i ), lda )
201  40 CONTINUE
202 *
203 * Reduce number of subdiagonals to K
204 *
205  DO 60 i = 1, n - 1 - k
206 *
207 * generate reflection to annihilate A(k+i+1:n,i)
208 *
209  wn = snrm2( n-k-i+1, a( k+i, i ), 1 )
210  wa = sign( wn, a( k+i, i ) )
211  IF( wn.EQ.zero ) THEN
212  tau = zero
213  ELSE
214  wb = a( k+i, i ) + wa
215  CALL sscal( n-k-i, one / wb, a( k+i+1, i ), 1 )
216  a( k+i, i ) = one
217  tau = wb / wa
218  END IF
219 *
220 * apply reflection to A(k+i:n,i+1:k+i-1) from the left
221 *
222  CALL sgemv( 'Transpose', n-k-i+1, k-1, one, a( k+i, i+1 ), lda,
223  $ a( k+i, i ), 1, zero, work, 1 )
224  CALL sger( n-k-i+1, k-1, -tau, a( k+i, i ), 1, work, 1,
225  $ a( k+i, i+1 ), lda )
226 *
227 * apply reflection to A(k+i:n,k+i:n) from the left and the right
228 *
229 * compute y := tau * A * u
230 *
231  CALL ssymv( 'Lower', n-k-i+1, tau, a( k+i, k+i ), lda,
232  $ a( k+i, i ), 1, zero, work, 1 )
233 *
234 * compute v := y - 1/2 * tau * ( y, u ) * u
235 *
236  alpha = -half*tau*sdot( n-k-i+1, work, 1, a( k+i, i ), 1 )
237  CALL saxpy( n-k-i+1, alpha, a( k+i, i ), 1, work, 1 )
238 *
239 * apply symmetric rank-2 update to A(k+i:n,k+i:n)
240 *
241  CALL ssyr2( 'Lower', n-k-i+1, -one, a( k+i, i ), 1, work, 1,
242  $ a( k+i, k+i ), lda )
243 *
244  a( k+i, i ) = -wa
245  DO 50 j = k + i + 1, n
246  a( j, i ) = zero
247  50 CONTINUE
248  60 CONTINUE
249 *
250 * Store full symmetric matrix
251 *
252  DO 80 j = 1, n
253  DO 70 i = j + 1, n
254  a( j, i ) = a( i, j )
255  70 CONTINUE
256  80 CONTINUE
257  RETURN
258 *
259 * End of SLAGSY
260 *
261  END
subroutine ssyr2(UPLO, N, ALPHA, X, INCX, Y, INCY, A, LDA)
SSYR2
Definition: ssyr2.f:149
subroutine sger(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
SGER
Definition: sger.f:132
subroutine slarnv(IDIST, ISEED, N, X)
SLARNV returns a vector of random numbers from a uniform or normal distribution.
Definition: slarnv.f:99
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine sgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
SGEMV
Definition: sgemv.f:158
subroutine slagsy(N, K, D, A, LDA, ISEED, WORK, INFO)
SLAGSY
Definition: slagsy.f:103
subroutine saxpy(N, SA, SX, INCX, SY, INCY)
SAXPY
Definition: saxpy.f:54
subroutine sscal(N, SA, SX, INCX)
SSCAL
Definition: sscal.f:55
subroutine ssymv(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
SSYMV
Definition: ssymv.f:154