LAPACK 3.11.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dgemv()

subroutine dgemv ( character  TRANS,
integer  M,
integer  N,
double precision  ALPHA,
double precision, dimension(lda,*)  A,
integer  LDA,
double precision, dimension(*)  X,
integer  INCX,
double precision  BETA,
double precision, dimension(*)  Y,
integer  INCY 
)

DGEMV

Purpose:
 DGEMV  performs one of the matrix-vector operations

    y := alpha*A*x + beta*y,   or   y := alpha*A**T*x + beta*y,

 where alpha and beta are scalars, x and y are vectors and A is an
 m by n matrix.
Parameters
[in]TRANS
          TRANS is CHARACTER*1
           On entry, TRANS specifies the operation to be performed as
           follows:

              TRANS = 'N' or 'n'   y := alpha*A*x + beta*y.

              TRANS = 'T' or 't'   y := alpha*A**T*x + beta*y.

              TRANS = 'C' or 'c'   y := alpha*A**T*x + beta*y.
[in]M
          M is INTEGER
           On entry, M specifies the number of rows of the matrix A.
           M must be at least zero.
[in]N
          N is INTEGER
           On entry, N specifies the number of columns of the matrix A.
           N must be at least zero.
[in]ALPHA
          ALPHA is DOUBLE PRECISION.
           On entry, ALPHA specifies the scalar alpha.
[in]A
          A is DOUBLE PRECISION array, dimension ( LDA, N )
           Before entry, the leading m by n part of the array A must
           contain the matrix of coefficients.
[in]LDA
          LDA is INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in the calling (sub) program. LDA must be at least
           max( 1, m ).
[in]X
          X is DOUBLE PRECISION array, dimension at least
           ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'
           and at least
           ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.
           Before entry, the incremented array X must contain the
           vector x.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
[in]BETA
          BETA is DOUBLE PRECISION.
           On entry, BETA specifies the scalar beta. When BETA is
           supplied as zero then Y need not be set on input.
[in,out]Y
          Y is DOUBLE PRECISION array, dimension at least
           ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'
           and at least
           ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.
           Before entry with BETA non-zero, the incremented array Y
           must contain the vector y. On exit, Y is overwritten by the
           updated vector y.
[in]INCY
          INCY is INTEGER
           On entry, INCY specifies the increment for the elements of
           Y. INCY must not be zero.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  Level 2 Blas routine.
  The vector and matrix arguments are not referenced when N = 0, or M = 0

  -- Written on 22-October-1986.
     Jack Dongarra, Argonne National Lab.
     Jeremy Du Croz, Nag Central Office.
     Sven Hammarling, Nag Central Office.
     Richard Hanson, Sandia National Labs.

Definition at line 155 of file dgemv.f.

156*
157* -- Reference BLAS level2 routine --
158* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
159* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
160*
161* .. Scalar Arguments ..
162 DOUBLE PRECISION ALPHA,BETA
163 INTEGER INCX,INCY,LDA,M,N
164 CHARACTER TRANS
165* ..
166* .. Array Arguments ..
167 DOUBLE PRECISION A(LDA,*),X(*),Y(*)
168* ..
169*
170* =====================================================================
171*
172* .. Parameters ..
173 DOUBLE PRECISION ONE,ZERO
174 parameter(one=1.0d+0,zero=0.0d+0)
175* ..
176* .. Local Scalars ..
177 DOUBLE PRECISION TEMP
178 INTEGER I,INFO,IX,IY,J,JX,JY,KX,KY,LENX,LENY
179* ..
180* .. External Functions ..
181 LOGICAL LSAME
182 EXTERNAL lsame
183* ..
184* .. External Subroutines ..
185 EXTERNAL xerbla
186* ..
187* .. Intrinsic Functions ..
188 INTRINSIC max
189* ..
190*
191* Test the input parameters.
192*
193 info = 0
194 IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
195 + .NOT.lsame(trans,'C')) THEN
196 info = 1
197 ELSE IF (m.LT.0) THEN
198 info = 2
199 ELSE IF (n.LT.0) THEN
200 info = 3
201 ELSE IF (lda.LT.max(1,m)) THEN
202 info = 6
203 ELSE IF (incx.EQ.0) THEN
204 info = 8
205 ELSE IF (incy.EQ.0) THEN
206 info = 11
207 END IF
208 IF (info.NE.0) THEN
209 CALL xerbla('DGEMV ',info)
210 RETURN
211 END IF
212*
213* Quick return if possible.
214*
215 IF ((m.EQ.0) .OR. (n.EQ.0) .OR.
216 + ((alpha.EQ.zero).AND. (beta.EQ.one))) RETURN
217*
218* Set LENX and LENY, the lengths of the vectors x and y, and set
219* up the start points in X and Y.
220*
221 IF (lsame(trans,'N')) THEN
222 lenx = n
223 leny = m
224 ELSE
225 lenx = m
226 leny = n
227 END IF
228 IF (incx.GT.0) THEN
229 kx = 1
230 ELSE
231 kx = 1 - (lenx-1)*incx
232 END IF
233 IF (incy.GT.0) THEN
234 ky = 1
235 ELSE
236 ky = 1 - (leny-1)*incy
237 END IF
238*
239* Start the operations. In this version the elements of A are
240* accessed sequentially with one pass through A.
241*
242* First form y := beta*y.
243*
244 IF (beta.NE.one) THEN
245 IF (incy.EQ.1) THEN
246 IF (beta.EQ.zero) THEN
247 DO 10 i = 1,leny
248 y(i) = zero
249 10 CONTINUE
250 ELSE
251 DO 20 i = 1,leny
252 y(i) = beta*y(i)
253 20 CONTINUE
254 END IF
255 ELSE
256 iy = ky
257 IF (beta.EQ.zero) THEN
258 DO 30 i = 1,leny
259 y(iy) = zero
260 iy = iy + incy
261 30 CONTINUE
262 ELSE
263 DO 40 i = 1,leny
264 y(iy) = beta*y(iy)
265 iy = iy + incy
266 40 CONTINUE
267 END IF
268 END IF
269 END IF
270 IF (alpha.EQ.zero) RETURN
271 IF (lsame(trans,'N')) THEN
272*
273* Form y := alpha*A*x + y.
274*
275 jx = kx
276 IF (incy.EQ.1) THEN
277 DO 60 j = 1,n
278 temp = alpha*x(jx)
279 DO 50 i = 1,m
280 y(i) = y(i) + temp*a(i,j)
281 50 CONTINUE
282 jx = jx + incx
283 60 CONTINUE
284 ELSE
285 DO 80 j = 1,n
286 temp = alpha*x(jx)
287 iy = ky
288 DO 70 i = 1,m
289 y(iy) = y(iy) + temp*a(i,j)
290 iy = iy + incy
291 70 CONTINUE
292 jx = jx + incx
293 80 CONTINUE
294 END IF
295 ELSE
296*
297* Form y := alpha*A**T*x + y.
298*
299 jy = ky
300 IF (incx.EQ.1) THEN
301 DO 100 j = 1,n
302 temp = zero
303 DO 90 i = 1,m
304 temp = temp + a(i,j)*x(i)
305 90 CONTINUE
306 y(jy) = y(jy) + alpha*temp
307 jy = jy + incy
308 100 CONTINUE
309 ELSE
310 DO 120 j = 1,n
311 temp = zero
312 ix = kx
313 DO 110 i = 1,m
314 temp = temp + a(i,j)*x(ix)
315 ix = ix + incx
316 110 CONTINUE
317 y(jy) = y(jy) + alpha*temp
318 jy = jy + incy
319 120 CONTINUE
320 END IF
321 END IF
322*
323 RETURN
324*
325* End of DGEMV
326*
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:53
Here is the call graph for this function: