LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
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, 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, 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, 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*> If either m or n is zero, then Y not referenced and the function
121*> performs a quick return.
122*> \endverbatim
123*>
124*> \param[in] INCY
125*> \verbatim
126*> INCY is INTEGER
127*> On entry, INCY specifies the increment for the elements of
128*> Y. INCY must not be zero.
129*> \endverbatim
130*
131* Authors:
132* ========
133*
134*> \author Univ. of Tennessee
135*> \author Univ. of California Berkeley
136*> \author Univ. of Colorado Denver
137*> \author NAG Ltd.
138*
139*> \ingroup gemv
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 --
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*
163* .. Scalar Arguments ..
164 DOUBLE PRECISION ALPHA,BETA
165 INTEGER INCX,INCY,LDA,M,N
166 CHARACTER TRANS
167* ..
168* .. Array Arguments ..
169 DOUBLE PRECISION A(LDA,*),X(*),Y(*)
170* ..
171*
172* =====================================================================
173*
174* .. Parameters ..
175 DOUBLE PRECISION ONE,ZERO
176 parameter(one=1.0d+0,zero=0.0d+0)
177* ..
178* .. Local Scalars ..
179 DOUBLE PRECISION TEMP
180 INTEGER I,INFO,IX,IY,J,JX,JY,KX,KY,LENX,LENY
181* ..
182* .. External Functions ..
183 LOGICAL LSAME
184 EXTERNAL lsame
185* ..
186* .. External Subroutines ..
187 EXTERNAL xerbla
188* ..
189* .. Intrinsic Functions ..
190 INTRINSIC max
191* ..
192*
193* Test the input parameters.
194*
195 info = 0
196 IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
197 + .NOT.lsame(trans,'C')) THEN
198 info = 1
199 ELSE IF (m.LT.0) THEN
200 info = 2
201 ELSE IF (n.LT.0) THEN
202 info = 3
203 ELSE IF (lda.LT.max(1,m)) THEN
204 info = 6
205 ELSE IF (incx.EQ.0) THEN
206 info = 8
207 ELSE IF (incy.EQ.0) THEN
208 info = 11
209 END IF
210 IF (info.NE.0) THEN
211 CALL xerbla('DGEMV ',info)
212 RETURN
213 END IF
214*
215* Quick return if possible.
216*
217 IF ((m.EQ.0) .OR. (n.EQ.0) .OR.
218 + ((alpha.EQ.zero).AND. (beta.EQ.one))) RETURN
219*
220* Set LENX and LENY, the lengths of the vectors x and y, and set
221* up the start points in X and Y.
222*
223 IF (lsame(trans,'N')) THEN
224 lenx = n
225 leny = m
226 ELSE
227 lenx = m
228 leny = n
229 END IF
230 IF (incx.GT.0) THEN
231 kx = 1
232 ELSE
233 kx = 1 - (lenx-1)*incx
234 END IF
235 IF (incy.GT.0) THEN
236 ky = 1
237 ELSE
238 ky = 1 - (leny-1)*incy
239 END IF
240*
241* Start the operations. In this version the elements of A are
242* accessed sequentially with one pass through A.
243*
244* First form y := beta*y.
245*
246 IF (beta.NE.one) THEN
247 IF (incy.EQ.1) THEN
248 IF (beta.EQ.zero) THEN
249 DO 10 i = 1,leny
250 y(i) = zero
251 10 CONTINUE
252 ELSE
253 DO 20 i = 1,leny
254 y(i) = beta*y(i)
255 20 CONTINUE
256 END IF
257 ELSE
258 iy = ky
259 IF (beta.EQ.zero) THEN
260 DO 30 i = 1,leny
261 y(iy) = zero
262 iy = iy + incy
263 30 CONTINUE
264 ELSE
265 DO 40 i = 1,leny
266 y(iy) = beta*y(iy)
267 iy = iy + incy
268 40 CONTINUE
269 END IF
270 END IF
271 END IF
272 IF (alpha.EQ.zero) RETURN
273 IF (lsame(trans,'N')) THEN
274*
275* Form y := alpha*A*x + y.
276*
277 jx = kx
278 IF (incy.EQ.1) THEN
279 DO 60 j = 1,n
280 temp = alpha*x(jx)
281 DO 50 i = 1,m
282 y(i) = y(i) + temp*a(i,j)
283 50 CONTINUE
284 jx = jx + incx
285 60 CONTINUE
286 ELSE
287 DO 80 j = 1,n
288 temp = alpha*x(jx)
289 iy = ky
290 DO 70 i = 1,m
291 y(iy) = y(iy) + temp*a(i,j)
292 iy = iy + incy
293 70 CONTINUE
294 jx = jx + incx
295 80 CONTINUE
296 END IF
297 ELSE
298*
299* Form y := alpha*A**T*x + y.
300*
301 jy = ky
302 IF (incx.EQ.1) THEN
303 DO 100 j = 1,n
304 temp = zero
305 DO 90 i = 1,m
306 temp = temp + a(i,j)*x(i)
307 90 CONTINUE
308 y(jy) = y(jy) + alpha*temp
309 jy = jy + incy
310 100 CONTINUE
311 ELSE
312 DO 120 j = 1,n
313 temp = zero
314 ix = kx
315 DO 110 i = 1,m
316 temp = temp + a(i,j)*x(ix)
317 ix = ix + incx
318 110 CONTINUE
319 y(jy) = y(jy) + alpha*temp
320 jy = jy + incy
321 120 CONTINUE
322 END IF
323 END IF
324*
325 RETURN
326*
327* End of DGEMV
328*
329 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dgemv(trans, m, n, alpha, a, lda, x, incx, beta, y, incy)
DGEMV
Definition dgemv.f:158