DGEMV performs one of the matrix-vector operations y := alphaAx + betay, or y := alphaATx + betay, where alpha and beta are scalars, x and y are vectors and A is an m by n matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | trans | |||
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
real(kind=dp), | intent(in) | :: | alpha | |||
real(kind=dp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
real(kind=dp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
real(kind=dp), | intent(in) | :: | beta | |||
real(kind=dp), | intent(inout) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
pure subroutine stdlib_dgemv(trans,m,n,alpha,a,lda,x,incx,beta,y,incy) !! 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. ! -- reference blas level2 routine -- ! -- reference blas is a software package provided by univ. of tennessee, -- ! -- univ. of california berkeley, univ. of colorado denver and nag ltd..-- ! Scalar Arguments real(dp), intent(in) :: alpha, beta integer(ilp), intent(in) :: incx, incy, lda, m, n character, intent(in) :: trans ! Array Arguments real(dp), intent(in) :: a(lda,*), x(*) real(dp), intent(inout) :: y(*) ! ===================================================================== ! Local Scalars real(dp) :: temp integer(ilp) :: i, info, ix, iy, j, jx, jy, kx, ky, lenx, leny ! Intrinsic Functions intrinsic :: max ! test the input parameters. info = 0 if (.not.stdlib_lsame(trans,'N') .and. .not.stdlib_lsame(trans,'T') & .and..not.stdlib_lsame(trans,'C')) then info = 1 else if (m<0) then info = 2 else if (n<0) then info = 3 else if (lda<max(1,m)) then info = 6 else if (incx==0) then info = 8 else if (incy==0) then info = 11 end if if (info/=0) then call stdlib_xerbla('DGEMV ',info) return end if ! quick return if possible. if ((m==0) .or. (n==0) .or.((alpha==zero).and. (beta==one))) return ! set lenx and leny, the lengths of the vectors x and y, and set ! up the start points in x and y. if (stdlib_lsame(trans,'N')) then lenx = n leny = m else lenx = m leny = n end if if (incx>0) then kx = 1 else kx = 1 - (lenx-1)*incx end if if (incy>0) then ky = 1 else ky = 1 - (leny-1)*incy end if ! start the operations. in this version the elements of a are ! accessed sequentially with one pass through a. ! first form y := beta*y. if (beta/=one) then if (incy==1) then if (beta==zero) then do i = 1,leny y(i) = zero end do else do i = 1,leny y(i) = beta*y(i) end do end if else iy = ky if (beta==zero) then do i = 1,leny y(iy) = zero iy = iy + incy end do else do i = 1,leny y(iy) = beta*y(iy) iy = iy + incy end do end if end if end if if (alpha==zero) return if (stdlib_lsame(trans,'N')) then ! form y := alpha*a*x + y. jx = kx if (incy==1) then do j = 1,n temp = alpha*x(jx) do i = 1,m y(i) = y(i) + temp*a(i,j) end do jx = jx + incx end do else do j = 1,n temp = alpha*x(jx) iy = ky do i = 1,m y(iy) = y(iy) + temp*a(i,j) iy = iy + incy end do jx = jx + incx end do end if else ! form y := alpha*a**t*x + y. jy = ky if (incx==1) then do j = 1,n temp = zero do i = 1,m temp = temp + a(i,j)*x(i) end do y(jy) = y(jy) + alpha*temp jy = jy + incy end do else do j = 1,n temp = zero ix = kx do i = 1,m temp = temp + a(i,j)*x(ix) ix = ix + incx end do y(jy) = y(jy) + alpha*temp jy = jy + incy end do end if end if return end subroutine stdlib_dgemv