You can not select more than 25 topics Topics must start with a chinese character,a letter or number, can include dashes ('-') and can be up to 35 characters long.

dlagsy.f 7.0 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261
  1. *> \brief \b DLAGSY
  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 DLAGSY( 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. * DOUBLE PRECISION A( LDA, * ), D( * ), WORK( * )
  19. * ..
  20. *
  21. *
  22. *> \par Purpose:
  23. * =============
  24. *>
  25. *> \verbatim
  26. *>
  27. *> DLAGSY 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 DOUBLE PRECISION array, dimension (N)
  52. *> The diagonal elements of the diagonal matrix D.
  53. *> \endverbatim
  54. *>
  55. *> \param[out] A
  56. *> \verbatim
  57. *> A is DOUBLE PRECISION 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 DOUBLE PRECISION 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 December 2016
  98. *
  99. *> \ingroup double_matgen
  100. *
  101. * =====================================================================
  102. SUBROUTINE DLAGSY( N, K, D, A, LDA, ISEED, WORK, INFO )
  103. *
  104. * -- LAPACK auxiliary routine (version 3.7.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. * December 2016
  108. *
  109. * .. Scalar Arguments ..
  110. INTEGER INFO, K, LDA, N
  111. * ..
  112. * .. Array Arguments ..
  113. INTEGER ISEED( 4 )
  114. DOUBLE PRECISION A( LDA, * ), D( * ), WORK( * )
  115. * ..
  116. *
  117. * =====================================================================
  118. *
  119. * .. Parameters ..
  120. DOUBLE PRECISION ZERO, ONE, HALF
  121. PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0, HALF = 0.5D+0 )
  122. * ..
  123. * .. Local Scalars ..
  124. INTEGER I, J
  125. DOUBLE PRECISION ALPHA, TAU, WA, WB, WN
  126. * ..
  127. * .. External Subroutines ..
  128. EXTERNAL DAXPY, DGEMV, DGER, DLARNV, DSCAL, DSYMV,
  129. $ DSYR2, XERBLA
  130. * ..
  131. * .. External Functions ..
  132. DOUBLE PRECISION DDOT, DNRM2
  133. EXTERNAL DDOT, DNRM2
  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( 'DLAGSY', -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 DLARNV( 3, ISEED, N-I+1, WORK )
  173. WN = DNRM2( 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 DSCAL( 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 DSYMV( '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*DDOT( N-I+1, WORK( N+1 ), 1, WORK, 1 )
  195. CALL DAXPY( 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 DSYR2( '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 = DNRM2( 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 DSCAL( 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 DGEMV( '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 DGER( 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 DSYMV( '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*DDOT( N-K-I+1, WORK, 1, A( K+I, I ), 1 )
  237. CALL DAXPY( 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 DSYR2( '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 DLAGSY
  260. *
  261. END