ZHEMV performs the matrix-vector operation y := alphaAx + beta*y, where alpha and beta are scalars, x and y are n element vectors and A is an n by n hermitian matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
character(len=1), | intent(in) | :: | uplo | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=dp), | intent(in) | :: | alpha | |||
complex(kind=dp), | intent(in) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda | |||
complex(kind=dp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=dp), | intent(in) | :: | beta | |||
complex(kind=dp), | intent(inout) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
pure subroutine stdlib_zhemv(uplo,n,alpha,a,lda,x,incx,beta,y,incy) !! ZHEMV performs the matrix-vector operation !! y := alpha*A*x + beta*y, !! where alpha and beta are scalars, x and y are n element vectors and !! A is an n by n hermitian 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 complex(dp), intent(in) :: alpha, beta integer(ilp), intent(in) :: incx, incy, lda, n character, intent(in) :: uplo ! Array Arguments complex(dp), intent(in) :: a(lda,*), x(*) complex(dp), intent(inout) :: y(*) ! ===================================================================== ! Local Scalars complex(dp) :: temp1, temp2 integer(ilp) :: i, info, ix, iy, j, jx, jy, kx, ky ! Intrinsic Functions intrinsic :: real,conjg,max ! test the input parameters. info = 0 if (.not.stdlib_lsame(uplo,'U') .and. .not.stdlib_lsame(uplo,'L')) then info = 1 else if (n<0) then info = 2 else if (lda<max(1,n)) then info = 5 else if (incx==0) then info = 7 else if (incy==0) then info = 10 end if if (info/=0) then call stdlib_xerbla('ZHEMV ',info) return end if ! quick return if possible. if ((n==0) .or. ((alpha==czero).and. (beta==cone))) return ! set up the start points in x and y. if (incx>0) then kx = 1 else kx = 1 - (n-1)*incx end if if (incy>0) then ky = 1 else ky = 1 - (n-1)*incy end if ! start the operations. in this version the elements of a are ! accessed sequentially with cone pass through the triangular part ! of a. ! first form y := beta*y. if (beta/=cone) then if (incy==1) then if (beta==czero) then do i = 1,n y(i) = czero end do else do i = 1,n y(i) = beta*y(i) end do end if else iy = ky if (beta==czero) then do i = 1,n y(iy) = czero iy = iy + incy end do else do i = 1,n y(iy) = beta*y(iy) iy = iy + incy end do end if end if end if if (alpha==czero) return if (stdlib_lsame(uplo,'U')) then ! form y when a is stored in upper triangle. if ((incx==1) .and. (incy==1)) then do j = 1,n temp1 = alpha*x(j) temp2 = czero do i = 1,j - 1 y(i) = y(i) + temp1*a(i,j) temp2 = temp2 + conjg(a(i,j))*x(i) end do y(j) = y(j) + temp1*real(a(j,j),KIND=dp) + alpha*temp2 end do else jx = kx jy = ky do j = 1,n temp1 = alpha*x(jx) temp2 = czero ix = kx iy = ky do i = 1,j - 1 y(iy) = y(iy) + temp1*a(i,j) temp2 = temp2 + conjg(a(i,j))*x(ix) ix = ix + incx iy = iy + incy end do y(jy) = y(jy) + temp1*real(a(j,j),KIND=dp) + alpha*temp2 jx = jx + incx jy = jy + incy end do end if else ! form y when a is stored in lower triangle. if ((incx==1) .and. (incy==1)) then do j = 1,n temp1 = alpha*x(j) temp2 = czero y(j) = y(j) + temp1*real(a(j,j),KIND=dp) do i = j + 1,n y(i) = y(i) + temp1*a(i,j) temp2 = temp2 + conjg(a(i,j))*x(i) end do y(j) = y(j) + alpha*temp2 end do else jx = kx jy = ky do j = 1,n temp1 = alpha*x(jx) temp2 = czero y(jy) = y(jy) + temp1*real(a(j,j),KIND=dp) ix = jx iy = jy do i = j + 1,n ix = ix + incx iy = iy + incy y(iy) = y(iy) + temp1*a(i,j) temp2 = temp2 + conjg(a(i,j))*x(ix) end do y(jy) = y(jy) + alpha*temp2 jx = jx + incx jy = jy + incy end do end if end if return end subroutine stdlib_zhemv