Télécharger dsymv.eso

Retour à la liste

Numérotation des lignes :

dsymv
  1. C DSYMV SOURCE BP208322 22/09/16 21:15:07 11454
  2. *> \brief \b DSYMV
  3. *
  4. * =========== DOCUMENTATION ===========
  5. *
  6. * Online html documentation available at
  7. * http://www.netlib.org/lapack/explore-html/
  8. *
  9. * Definition:
  10. * ===========
  11. *
  12. * SUBROUTINE DSYMV(UPLO,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
  13. *
  14. * .. Scalar Arguments ..
  15. * REAL*8 ALPHA,BETA
  16. * INTEGER INCX,INCY,LDA,N
  17. * CHARACTER UPLO
  18. * ..
  19. * .. Array Arguments ..
  20. * REAL*8 A(LDA,*),X(*),Y(*)
  21. * ..
  22. *
  23. *
  24. *> \par Purpose:
  25. * =============
  26. *>
  27. *> \verbatim
  28. *>
  29. *> DSYMV performs the matrix-vector operation
  30. *>
  31. *> y := alpha*A*x + beta*y,
  32. *>
  33. *> where alpha and beta are scalars, x and y are n element vectors and
  34. *> A is an n by n symmetric matrix.
  35. *> \endverbatim
  36. *
  37. * Arguments:
  38. * ==========
  39. *
  40. *> \param[in] UPLO
  41. *> \verbatim
  42. *> UPLO is CHARACTER*1
  43. *> On entry, UPLO specifies whether the upper or lower
  44. *> triangular part of the array A is to be referenced as
  45. *> follows:
  46. *>
  47. *> UPLO = 'U' or 'u' Only the upper triangular part of A
  48. *> is to be referenced.
  49. *>
  50. *> UPLO = 'L' or 'l' Only the lower triangular part of A
  51. *> is to be referenced.
  52. *> \endverbatim
  53. *>
  54. *> \param[in] N
  55. *> \verbatim
  56. *> N is INTEGER
  57. *> On entry, N specifies the order of the matrix A.
  58. *> N must be at least zero.
  59. *> \endverbatim
  60. *>
  61. *> \param[in] ALPHA
  62. *> \verbatim
  63. *> ALPHA is REAL*8.
  64. *> On entry, ALPHA specifies the scalar alpha.
  65. *> \endverbatim
  66. *>
  67. *> \param[in] A
  68. *> \verbatim
  69. *> A is REAL*8 array, dimension ( LDA, N )
  70. *> Before entry with UPLO = 'U' or 'u', the leading n by n
  71. *> upper triangular part of the array A must contain the upper
  72. *> triangular part of the symmetric matrix and the strictly
  73. *> lower triangular part of A is not referenced.
  74. *> Before entry with UPLO = 'L' or 'l', the leading n by n
  75. *> lower triangular part of the array A must contain the lower
  76. *> triangular part of the symmetric matrix and the strictly
  77. *> upper triangular part of A is not referenced.
  78. *> \endverbatim
  79. *>
  80. *> \param[in] LDA
  81. *> \verbatim
  82. *> LDA is INTEGER
  83. *> On entry, LDA specifies the first dimension of A as declared
  84. *> in the calling (sub) program. LDA must be at least
  85. *> max( 1, n ).
  86. *> \endverbatim
  87. *>
  88. *> \param[in] X
  89. *> \verbatim
  90. *> X is REAL*8 array, dimension at least
  91. *> ( 1 + ( n - 1 )*abs( INCX ) ).
  92. *> Before entry, the incremented array X must contain the n
  93. *> element vector x.
  94. *> \endverbatim
  95. *>
  96. *> \param[in] INCX
  97. *> \verbatim
  98. *> INCX is INTEGER
  99. *> On entry, INCX specifies the increment for the elements of
  100. *> X. INCX must not be zero.
  101. *> \endverbatim
  102. *>
  103. *> \param[in] BETA
  104. *> \verbatim
  105. *> BETA is REAL*8.
  106. *> On entry, BETA specifies the scalar beta. When BETA is
  107. *> supplied as zero then Y need not be set on input.
  108. *> \endverbatim
  109. *>
  110. *> \param[in,out] Y
  111. *> \verbatim
  112. *> Y is REAL*8 array, dimension at least
  113. *> ( 1 + ( n - 1 )*abs( INCY ) ).
  114. *> Before entry, the incremented array Y must contain the n
  115. *> element vector y. On exit, Y is overwritten by the updated
  116. *> vector y.
  117. *> \endverbatim
  118. *>
  119. *> \param[in] INCY
  120. *> \verbatim
  121. *> INCY is INTEGER
  122. *> On entry, INCY specifies the increment for the elements of
  123. *> Y. INCY must not be zero.
  124. *> \endverbatim
  125. *
  126. * Authors:
  127. * ========
  128. *
  129. *> \author Univ. of Tennessee
  130. *> \author Univ. of California Berkeley
  131. *> \author Univ. of Colorado Denver
  132. *> \author NAG Ltd.
  133. *
  134. *> \ingroup double_blas_level2
  135. *
  136. *> \par Further Details:
  137. * =====================
  138. *>
  139. *> \verbatim
  140. *>
  141. *> Level 2 Blas routine.
  142. *> The vector and matrix arguments are not referenced when N = 0, or M = 0
  143. *>
  144. *> -- Written on 22-October-1986.
  145. *> Jack Dongarra, Argonne National Lab.
  146. *> Jeremy Du Croz, Nag Central Office.
  147. *> Sven Hammarling, Nag Central Office.
  148. *> Richard Hanson, Sandia National Labs.
  149. *> \endverbatim
  150. *>
  151. * =====================================================================
  152. SUBROUTINE DSYMV(UPLO,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
  153. *
  154. * -- Reference BLAS level2 routine --
  155. * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
  156. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  157. *
  158. * .. Scalar Arguments ..
  159. REAL*8 ALPHA,BETA
  160. INTEGER INCX,INCY,LDA,N
  161. CHARACTER UPLO
  162. * ..
  163. * .. Array Arguments ..
  164. REAL*8 A(LDA,*),X(*),Y(*)
  165. * ..
  166. *
  167. * =====================================================================
  168. *
  169. * .. Parameters ..
  170. REAL*8 ONE,ZERO
  171. PARAMETER (ONE=1.0D+0,ZERO=0.0D+0)
  172. * ..
  173. * .. Local Scalars ..
  174. REAL*8 TEMP1,TEMP2
  175. INTEGER I,INFO,IX,IY,J,JX,JY,KX,KY
  176. * ..
  177. * .. External Functions ..
  178. LOGICAL LSAME
  179. EXTERNAL LSAME
  180. * ..
  181. * .. External Subroutines ..
  182. EXTERNAL XERBLA
  183. * ..
  184. * .. Intrinsic Functions ..
  185. * INTRINSIC MAX
  186. * ..
  187. *
  188. * Test the input parameters.
  189. *
  190. INFO = 0
  191. IF (.NOT.LSAME(UPLO,'U') .AND. .NOT.LSAME(UPLO,'L')) THEN
  192. INFO = 1
  193. ELSE IF (N.LT.0) THEN
  194. INFO = 2
  195. ELSE IF (LDA.LT.MAX(1,N)) THEN
  196. INFO = 5
  197. ELSE IF (INCX.EQ.0) THEN
  198. INFO = 7
  199. ELSE IF (INCY.EQ.0) THEN
  200. INFO = 10
  201. END IF
  202. IF (INFO.NE.0) THEN
  203. CALL XERBLA('DSYMV ',INFO)
  204. RETURN
  205. END IF
  206. *
  207. * Quick return if possible.
  208. *
  209. IF ((N.EQ.0) .OR. ((ALPHA.EQ.ZERO).AND. (BETA.EQ.ONE))) RETURN
  210. *
  211. * Set up the start points in X and Y.
  212. *
  213. IF (INCX.GT.0) THEN
  214. KX = 1
  215. ELSE
  216. KX = 1 - (N-1)*INCX
  217. END IF
  218. IF (INCY.GT.0) THEN
  219. KY = 1
  220. ELSE
  221. KY = 1 - (N-1)*INCY
  222. END IF
  223. *
  224. * Start the operations. In this version the elements of A are
  225. * accessed sequentially with one pass through the triangular part
  226. * of A.
  227. *
  228. * First form y := beta*y.
  229. *
  230. IF (BETA.NE.ONE) THEN
  231. IF (INCY.EQ.1) THEN
  232. IF (BETA.EQ.ZERO) THEN
  233. DO 10 I = 1,N
  234. Y(I) = ZERO
  235. 10 CONTINUE
  236. ELSE
  237. DO 20 I = 1,N
  238. Y(I) = BETA*Y(I)
  239. 20 CONTINUE
  240. END IF
  241. ELSE
  242. IY = KY
  243. IF (BETA.EQ.ZERO) THEN
  244. DO 30 I = 1,N
  245. Y(IY) = ZERO
  246. IY = IY + INCY
  247. 30 CONTINUE
  248. ELSE
  249. DO 40 I = 1,N
  250. Y(IY) = BETA*Y(IY)
  251. IY = IY + INCY
  252. 40 CONTINUE
  253. END IF
  254. END IF
  255. END IF
  256. IF (ALPHA.EQ.ZERO) RETURN
  257. IF (LSAME(UPLO,'U')) THEN
  258. *
  259. * Form y when A is stored in upper triangle.
  260. *
  261. IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN
  262. DO 60 J = 1,N
  263. TEMP1 = ALPHA*X(J)
  264. TEMP2 = ZERO
  265. DO 50 I = 1,J - 1
  266. Y(I) = Y(I) + TEMP1*A(I,J)
  267. TEMP2 = TEMP2 + A(I,J)*X(I)
  268. 50 CONTINUE
  269. Y(J) = Y(J) + TEMP1*A(J,J) + ALPHA*TEMP2
  270. 60 CONTINUE
  271. ELSE
  272. JX = KX
  273. JY = KY
  274. DO 80 J = 1,N
  275. TEMP1 = ALPHA*X(JX)
  276. TEMP2 = ZERO
  277. IX = KX
  278. IY = KY
  279. DO 70 I = 1,J - 1
  280. Y(IY) = Y(IY) + TEMP1*A(I,J)
  281. TEMP2 = TEMP2 + A(I,J)*X(IX)
  282. IX = IX + INCX
  283. IY = IY + INCY
  284. 70 CONTINUE
  285. Y(JY) = Y(JY) + TEMP1*A(J,J) + ALPHA*TEMP2
  286. JX = JX + INCX
  287. JY = JY + INCY
  288. 80 CONTINUE
  289. END IF
  290. ELSE
  291. *
  292. * Form y when A is stored in lower triangle.
  293. *
  294. IF ((INCX.EQ.1) .AND. (INCY.EQ.1)) THEN
  295. DO 100 J = 1,N
  296. TEMP1 = ALPHA*X(J)
  297. TEMP2 = ZERO
  298. Y(J) = Y(J) + TEMP1*A(J,J)
  299. DO 90 I = J + 1,N
  300. Y(I) = Y(I) + TEMP1*A(I,J)
  301. TEMP2 = TEMP2 + A(I,J)*X(I)
  302. 90 CONTINUE
  303. Y(J) = Y(J) + ALPHA*TEMP2
  304. 100 CONTINUE
  305. ELSE
  306. JX = KX
  307. JY = KY
  308. DO 120 J = 1,N
  309. TEMP1 = ALPHA*X(JX)
  310. TEMP2 = ZERO
  311. Y(JY) = Y(JY) + TEMP1*A(J,J)
  312. IX = JX
  313. IY = JY
  314. DO 110 I = J + 1,N
  315. IX = IX + INCX
  316. IY = IY + INCY
  317. Y(IY) = Y(IY) + TEMP1*A(I,J)
  318. TEMP2 = TEMP2 + A(I,J)*X(IX)
  319. 110 CONTINUE
  320. Y(JY) = Y(JY) + ALPHA*TEMP2
  321. JX = JX + INCX
  322. JY = JY + INCY
  323. 120 CONTINUE
  324. END IF
  325. END IF
  326. *
  327. RETURN
  328. *
  329. * End of DSYMV
  330. *
  331. END
  332.  
  333.  

© Cast3M 2003 - Tous droits réservés.
Mentions légales