ssyr2.f 7.8 KB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237
  1. *DECK SSYR2
  2. SUBROUTINE SSYR2 (UPLO, N, ALPHA, X, INCX, Y, INCY, A, LDA)
  3. C***BEGIN PROLOGUE SSYR2
  4. C***PURPOSE Perform symmetric rank 2 update of a real symmetric matrix.
  5. C***LIBRARY SLATEC (BLAS)
  6. C***CATEGORY D1B4
  7. C***TYPE SINGLE PRECISION (SSYR2-S, DSYR2-D, CSYR2-C)
  8. C***KEYWORDS LEVEL 2 BLAS, LINEAR ALGEBRA
  9. C***AUTHOR Dongarra, J. J., (ANL)
  10. C Du Croz, J., (NAG)
  11. C Hammarling, S., (NAG)
  12. C Hanson, R. J., (SNLA)
  13. C***DESCRIPTION
  14. C
  15. C SSYR2 performs the symmetric rank 2 operation
  16. C
  17. C A := alpha*x*y' + alpha*y*x' + A,
  18. C
  19. C where alpha is a scalar, x and y are n element vectors and A is an n
  20. C by n symmetric matrix.
  21. C
  22. C Parameters
  23. C ==========
  24. C
  25. C UPLO - CHARACTER*1.
  26. C On entry, UPLO specifies whether the upper or lower
  27. C triangular part of the array A is to be referenced as
  28. C follows:
  29. C
  30. C UPLO = 'U' or 'u' Only the upper triangular part of A
  31. C is to be referenced.
  32. C
  33. C UPLO = 'L' or 'l' Only the lower triangular part of A
  34. C is to be referenced.
  35. C
  36. C Unchanged on exit.
  37. C
  38. C N - INTEGER.
  39. C On entry, N specifies the order of the matrix A.
  40. C N must be at least zero.
  41. C Unchanged on exit.
  42. C
  43. C ALPHA - REAL .
  44. C On entry, ALPHA specifies the scalar alpha.
  45. C Unchanged on exit.
  46. C
  47. C X - REAL array of dimension at least
  48. C ( 1 + ( n - 1)*abs( INCX)).
  49. C Before entry, the incremented array X must contain the n
  50. C element vector x.
  51. C Unchanged on exit.
  52. C
  53. C INCX - INTEGER.
  54. C On entry, INCX specifies the increment for the elements of
  55. C X. INCX must not be zero.
  56. C Unchanged on exit.
  57. C
  58. C Y - REAL array of dimension at least
  59. C ( 1 + ( n - 1 )*abs( INCY ) ).
  60. C Before entry, the incremented array Y must contain the n
  61. C element vector y.
  62. C Unchanged on exit.
  63. C
  64. C INCY - INTEGER.
  65. C On entry, INCY specifies the increment for the elements of
  66. C Y. INCY must not be zero.
  67. C Unchanged on exit.
  68. C
  69. C A - REAL array of DIMENSION ( LDA, n ).
  70. C Before entry with UPLO = 'U' or 'u', the leading n by n
  71. C upper triangular part of the array A must contain the upper
  72. C triangular part of the symmetric matrix and the strictly
  73. C lower triangular part of A is not referenced. On exit, the
  74. C upper triangular part of the array A is overwritten by the
  75. C upper triangular part of the updated matrix.
  76. C Before entry with UPLO = 'L' or 'l', the leading n by n
  77. C lower triangular part of the array A must contain the lower
  78. C triangular part of the symmetric matrix and the strictly
  79. C upper triangular part of A is not referenced. On exit, the
  80. C lower triangular part of the array A is overwritten by the
  81. C lower triangular part of the updated matrix.
  82. C
  83. C LDA - INTEGER.
  84. C On entry, LDA specifies the first dimension of A as declared
  85. C in the calling (sub) program. LDA must be at least
  86. C max( 1, n ).
  87. C Unchanged on exit.
  88. C
  89. C***REFERENCES Dongarra, J. J., Du Croz, J., Hammarling, S., and
  90. C Hanson, R. J. An extended set of Fortran basic linear
  91. C algebra subprograms. ACM TOMS, Vol. 14, No. 1,
  92. C pp. 1-17, March 1988.
  93. C***ROUTINES CALLED LSAME, XERBLA
  94. C***REVISION HISTORY (YYMMDD)
  95. C 861022 DATE WRITTEN
  96. C 910605 Modified to meet SLATEC prologue standards. Only comment
  97. C lines were modified. (BKS)
  98. C***END PROLOGUE SSYR2
  99. C .. Scalar Arguments ..
  100. REAL ALPHA
  101. INTEGER INCX, INCY, LDA, N
  102. CHARACTER*1 UPLO
  103. C .. Array Arguments ..
  104. REAL A( LDA, * ), X( * ), Y( * )
  105. C .. Parameters ..
  106. REAL ZERO
  107. PARAMETER ( ZERO = 0.0E+0 )
  108. C .. Local Scalars ..
  109. REAL TEMP1, TEMP2
  110. INTEGER I, INFO, IX, IY, J, JX, JY, KX, KY
  111. C .. External Functions ..
  112. LOGICAL LSAME
  113. EXTERNAL LSAME
  114. C .. External Subroutines ..
  115. EXTERNAL XERBLA
  116. C .. Intrinsic Functions ..
  117. INTRINSIC MAX
  118. C***FIRST EXECUTABLE STATEMENT SSYR2
  119. C
  120. C Test the input parameters.
  121. C
  122. INFO = 0
  123. IF ( .NOT.LSAME( UPLO, 'U' ).AND.
  124. $ .NOT.LSAME( UPLO, 'L' ) )THEN
  125. INFO = 1
  126. ELSE IF( N.LT.0 )THEN
  127. INFO = 2
  128. ELSE IF( INCX.EQ.0 )THEN
  129. INFO = 5
  130. ELSE IF( INCY.EQ.0 )THEN
  131. INFO = 7
  132. ELSE IF( LDA.LT.MAX( 1, N ) )THEN
  133. INFO = 9
  134. END IF
  135. IF( INFO.NE.0 )THEN
  136. CALL XERBLA( 'SSYR2 ', INFO )
  137. RETURN
  138. END IF
  139. C
  140. C Quick return if possible.
  141. C
  142. IF( ( N.EQ.0 ).OR.( ALPHA.EQ.ZERO ) )
  143. $ RETURN
  144. C
  145. C Set up the start points in X and Y if the increments are not both
  146. C unity.
  147. C
  148. IF( ( INCX.NE.1 ).OR.( INCY.NE.1 ) )THEN
  149. IF( INCX.GT.0 )THEN
  150. KX = 1
  151. ELSE
  152. KX = 1 - ( N - 1 )*INCX
  153. END IF
  154. IF( INCY.GT.0 )THEN
  155. KY = 1
  156. ELSE
  157. KY = 1 - ( N - 1 )*INCY
  158. END IF
  159. JX = KX
  160. JY = KY
  161. END IF
  162. C
  163. C Start the operations. In this version the elements of A are
  164. C accessed sequentially with one pass through the triangular part
  165. C of A.
  166. C
  167. IF( LSAME( UPLO, 'U' ) )THEN
  168. C
  169. C Form A when A is stored in the upper triangle.
  170. C
  171. IF( ( INCX.EQ.1 ).AND.( INCY.EQ.1 ) )THEN
  172. DO 20, J = 1, N
  173. IF( ( X( J ).NE.ZERO ).OR.( Y( J ).NE.ZERO ) )THEN
  174. TEMP1 = ALPHA*Y( J )
  175. TEMP2 = ALPHA*X( J )
  176. DO 10, I = 1, J
  177. A( I, J ) = A( I, J ) + X( I )*TEMP1 + Y( I )*TEMP2
  178. 10 CONTINUE
  179. END IF
  180. 20 CONTINUE
  181. ELSE
  182. DO 40, J = 1, N
  183. IF( ( X( JX ).NE.ZERO ).OR.( Y( JY ).NE.ZERO ) )THEN
  184. TEMP1 = ALPHA*Y( JY )
  185. TEMP2 = ALPHA*X( JX )
  186. IX = KX
  187. IY = KY
  188. DO 30, I = 1, J
  189. A( I, J ) = A( I, J ) + X( IX )*TEMP1
  190. $ + Y( IY )*TEMP2
  191. IX = IX + INCX
  192. IY = IY + INCY
  193. 30 CONTINUE
  194. END IF
  195. JX = JX + INCX
  196. JY = JY + INCY
  197. 40 CONTINUE
  198. END IF
  199. ELSE
  200. C
  201. C Form A when A is stored in the lower triangle.
  202. C
  203. IF( ( INCX.EQ.1 ).AND.( INCY.EQ.1 ) )THEN
  204. DO 60, J = 1, N
  205. IF( ( X( J ).NE.ZERO ).OR.( Y( J ).NE.ZERO ) )THEN
  206. TEMP1 = ALPHA*Y( J )
  207. TEMP2 = ALPHA*X( J )
  208. DO 50, I = J, N
  209. A( I, J ) = A( I, J ) + X( I )*TEMP1 + Y( I )*TEMP2
  210. 50 CONTINUE
  211. END IF
  212. 60 CONTINUE
  213. ELSE
  214. DO 80, J = 1, N
  215. IF( ( X( JX ).NE.ZERO ).OR.( Y( JY ).NE.ZERO ) )THEN
  216. TEMP1 = ALPHA*Y( JY )
  217. TEMP2 = ALPHA*X( JX )
  218. IX = JX
  219. IY = JY
  220. DO 70, I = J, N
  221. A( I, J ) = A( I, J ) + X( IX )*TEMP1
  222. $ + Y( IY )*TEMP2
  223. IX = IX + INCX
  224. IY = IY + INCY
  225. 70 CONTINUE
  226. END IF
  227. JX = JX + INCX
  228. JY = JY + INCY
  229. 80 CONTINUE
  230. END IF
  231. END IF
  232. C
  233. RETURN
  234. C
  235. C End of SSYR2 .
  236. C
  237. END