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