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.

dgemvf.f 7.4 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256
  1. SUBROUTINE DGEMVF ( TRANS, M, N, ALPHA, A, LDA, X, INCX,
  2. $ BETA, Y, INCY )
  3. * .. Scalar Arguments ..
  4. DOUBLE PRECISION ALPHA, BETA
  5. INTEGER INCX, INCY, LDA, M, N
  6. CHARACTER*1 TRANS
  7. * .. Array Arguments ..
  8. DOUBLE PRECISION A( LDA, * ), X( * ), Y( * )
  9. * ..
  10. *
  11. * Purpose
  12. * =======
  13. *
  14. * DGEMV performs one of the matrix-vector operations
  15. *
  16. * y := alpha*A*x + beta*y, or y := alpha*A'*x + beta*y,
  17. *
  18. * where alpha and beta are scalars, x and y are vectors and A is an
  19. * m by n matrix.
  20. *
  21. * Parameters
  22. * ==========
  23. *
  24. * TRANS - CHARACTER*1.
  25. * On entry, TRANS specifies the operation to be performed as
  26. * follows:
  27. *
  28. * TRANS = 'N' or 'n' y := alpha*A*x + beta*y.
  29. *
  30. * TRANS = 'T' or 't' y := alpha*A'*x + beta*y.
  31. *
  32. * TRANS = 'C' or 'c' y := alpha*A'*x + beta*y.
  33. *
  34. * Unchanged on exit.
  35. *
  36. * M - INTEGER.
  37. * On entry, M specifies the number of rows of the matrix A.
  38. * M must be at least zero.
  39. * Unchanged on exit.
  40. *
  41. * N - INTEGER.
  42. * On entry, N specifies the number of columns of the matrix A.
  43. * N must be at least zero.
  44. * Unchanged on exit.
  45. *
  46. * ALPHA - DOUBLE PRECISION.
  47. * On entry, ALPHA specifies the scalar alpha.
  48. * Unchanged on exit.
  49. *
  50. * A - DOUBLE PRECISION array of DIMENSION ( LDA, n ).
  51. * Before entry, the leading m by n part of the array A must
  52. * contain the matrix of coefficients.
  53. * Unchanged on exit.
  54. *
  55. * LDA - INTEGER.
  56. * On entry, LDA specifies the first dimension of A as declared
  57. * in the calling (sub) program. LDA must be at least
  58. * max( 1, m ).
  59. * Unchanged on exit.
  60. *
  61. * X - DOUBLE PRECISION array of DIMENSION at least
  62. * ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'
  63. * and at least
  64. * ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.
  65. * Before entry, the incremented array X must contain the
  66. * vector x.
  67. * Unchanged on exit.
  68. *
  69. * INCX - INTEGER.
  70. * On entry, INCX specifies the increment for the elements of
  71. * X. INCX must not be zero.
  72. * Unchanged on exit.
  73. *
  74. * BETA - DOUBLE PRECISION.
  75. * On entry, BETA specifies the scalar beta. When BETA is
  76. * supplied as zero then Y need not be set on input.
  77. * Unchanged on exit.
  78. *
  79. * Y - DOUBLE PRECISION array of DIMENSION at least
  80. * ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'
  81. * and at least
  82. * ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.
  83. * Before entry with BETA non-zero, the incremented array Y
  84. * must contain the vector y. On exit, Y is overwritten by the
  85. * updated vector y.
  86. *
  87. * INCY - INTEGER.
  88. * On entry, INCY specifies the increment for the elements of
  89. * Y. INCY must not be zero.
  90. * Unchanged on exit.
  91. *
  92. *
  93. * Level 2 Blas routine.
  94. *
  95. * -- Written on 22-October-1986.
  96. * Jack Dongarra, Argonne National Lab.
  97. * Jeremy Du Croz, Nag Central Office.
  98. * Sven Hammarling, Nag Central Office.
  99. * Richard Hanson, Sandia National Labs.
  100. *
  101. *
  102. * .. Parameters ..
  103. DOUBLE PRECISION ONE , ZERO
  104. PARAMETER ( ONE = 1.0D+0, ZERO = 0.0D+0 )
  105. * .. Local Scalars ..
  106. DOUBLE PRECISION TEMP
  107. INTEGER I, INFO, IX, IY, J, JX, JY, KX, KY, LENX, LENY
  108. * .. External Functions ..
  109. LOGICAL LSAME
  110. EXTERNAL LSAME
  111. * .. External Subroutines ..
  112. * .. Intrinsic Functions ..
  113. INTRINSIC MAX
  114. * ..
  115. * .. Executable Statements ..
  116. *
  117. * Test the input parameters.
  118. *
  119. INFO = 0
  120. IF ( .NOT.LSAME( TRANS, 'N' ).AND.
  121. $ .NOT.LSAME( TRANS, 'T' ).AND.
  122. $ .NOT.LSAME( TRANS, 'C' ) )THEN
  123. INFO = 1
  124. ELSE IF( M.LT.0 )THEN
  125. INFO = 2
  126. ELSE IF( N.LT.0 )THEN
  127. INFO = 3
  128. ELSE IF( LDA.LT.MAX( 1, M ) )THEN
  129. INFO = 6
  130. ELSE IF( INCX.EQ.0 )THEN
  131. INFO = 8
  132. ELSE IF( INCY.EQ.0 )THEN
  133. INFO = 11
  134. END IF
  135. *
  136. * Quick return if possible.
  137. *
  138. IF( ( M.EQ.0 ).OR.( N.EQ.0 ).OR.
  139. $ ( ( ALPHA.EQ.ZERO ).AND.( BETA.EQ.ONE ) ) )
  140. $ RETURN
  141. *
  142. * Set LENX and LENY, the lengths of the vectors x and y, and set
  143. * up the start points in X and Y.
  144. *
  145. IF( LSAME( TRANS, 'N' ) )THEN
  146. LENX = N
  147. LENY = M
  148. ELSE
  149. LENX = M
  150. LENY = N
  151. END IF
  152. IF( INCX.GT.0 )THEN
  153. KX = 1
  154. ELSE
  155. KX = 1 - ( LENX - 1 )*INCX
  156. END IF
  157. IF( INCY.GT.0 )THEN
  158. KY = 1
  159. ELSE
  160. KY = 1 - ( LENY - 1 )*INCY
  161. END IF
  162. *
  163. * Start the operations. In this version the elements of A are
  164. * accessed sequentially with one pass through A.
  165. *
  166. * First form y := beta*y.
  167. *
  168. IF( BETA.NE.ONE )THEN
  169. IF( INCY.EQ.1 )THEN
  170. IF( BETA.EQ.ZERO )THEN
  171. DO 10, I = 1, LENY
  172. Y( I ) = ZERO
  173. 10 CONTINUE
  174. ELSE
  175. DO 20, I = 1, LENY
  176. Y( I ) = BETA*Y( I )
  177. 20 CONTINUE
  178. END IF
  179. ELSE
  180. IY = KY
  181. IF( BETA.EQ.ZERO )THEN
  182. DO 30, I = 1, LENY
  183. Y( IY ) = ZERO
  184. IY = IY + INCY
  185. 30 CONTINUE
  186. ELSE
  187. DO 40, I = 1, LENY
  188. Y( IY ) = BETA*Y( IY )
  189. IY = IY + INCY
  190. 40 CONTINUE
  191. END IF
  192. END IF
  193. END IF
  194. IF( ALPHA.EQ.ZERO )
  195. $ RETURN
  196. IF( LSAME( TRANS, 'N' ) )THEN
  197. *
  198. * Form y := alpha*A*x + y.
  199. *
  200. JX = KX
  201. IF( INCY.EQ.1 )THEN
  202. DO 60, J = 1, N
  203. IF( X( JX ).NE.ZERO )THEN
  204. TEMP = ALPHA*X( JX )
  205. DO 50, I = 1, M
  206. Y( I ) = Y( I ) + TEMP*A( I, J )
  207. 50 CONTINUE
  208. END IF
  209. JX = JX + INCX
  210. 60 CONTINUE
  211. ELSE
  212. DO 80, J = 1, N
  213. IF( X( JX ).NE.ZERO )THEN
  214. TEMP = ALPHA*X( JX )
  215. IY = KY
  216. DO 70, I = 1, M
  217. Y( IY ) = Y( IY ) + TEMP*A( I, J )
  218. IY = IY + INCY
  219. 70 CONTINUE
  220. END IF
  221. JX = JX + INCX
  222. 80 CONTINUE
  223. END IF
  224. ELSE
  225. *
  226. * Form y := alpha*A'*x + y.
  227. *
  228. JY = KY
  229. IF( INCX.EQ.1 )THEN
  230. DO 100, J = 1, N
  231. TEMP = ZERO
  232. DO 90, I = 1, M
  233. TEMP = TEMP + A( I, J )*X( I )
  234. 90 CONTINUE
  235. Y( JY ) = Y( JY ) + ALPHA*TEMP
  236. JY = JY + INCY
  237. 100 CONTINUE
  238. ELSE
  239. DO 120, J = 1, N
  240. TEMP = ZERO
  241. IX = KX
  242. DO 110, I = 1, M
  243. TEMP = TEMP + A( I, J )*X( IX )
  244. IX = IX + INCX
  245. 110 CONTINUE
  246. Y( JY ) = Y( JY ) + ALPHA*TEMP
  247. JY = JY + INCY
  248. 120 CONTINUE
  249. END IF
  250. END IF
  251. *
  252. RETURN
  253. *
  254. * End of DGEMV .
  255. *
  256. END