ZHER performs the hermitian rank 1 operation A := alphaxx**H + A, where alpha is a real scalar, x is an n element vector 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 | |||
real(kind=dp), | intent(in) | :: | alpha | |||
complex(kind=dp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=dp), | intent(inout) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda |
pure subroutine stdlib_zher(uplo,n,alpha,x,incx,a,lda) !! ZHER performs the hermitian rank 1 operation !! A := alpha*x*x**H + A, !! where alpha is a real scalar, x is an n element vector 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 real(dp), intent(in) :: alpha integer(ilp), intent(in) :: incx, lda, n character, intent(in) :: uplo ! Array Arguments complex(dp), intent(inout) :: a(lda,*) complex(dp), intent(in) :: x(*) ! ===================================================================== ! Local Scalars complex(dp) :: temp integer(ilp) :: i, info, ix, j, jx, kx ! 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 (incx==0) then info = 5 else if (lda<max(1,n)) then info = 7 end if if (info/=0) then call stdlib_xerbla('ZHER ',info) return end if ! quick return if possible. if ((n==0) .or. (alpha==real(czero,KIND=dp))) return ! set the start point in x if the increment is not unity. if (incx<=0) then kx = 1 - (n-1)*incx else if (incx/=1) then kx = 1 end if ! start the operations. in this version the elements of a are ! accessed sequentially with cone pass through the triangular part ! of a. if (stdlib_lsame(uplo,'U')) then ! form a when a is stored in upper triangle. if (incx==1) then do j = 1,n if (x(j)/=czero) then temp = alpha*conjg(x(j)) do i = 1,j - 1 a(i,j) = a(i,j) + x(i)*temp end do a(j,j) = real(a(j,j),KIND=dp) + real(x(j)*temp,KIND=dp) else a(j,j) = real(a(j,j),KIND=dp) end if end do else jx = kx do j = 1,n if (x(jx)/=czero) then temp = alpha*conjg(x(jx)) ix = kx do i = 1,j - 1 a(i,j) = a(i,j) + x(ix)*temp ix = ix + incx end do a(j,j) = real(a(j,j),KIND=dp) + real(x(jx)*temp,KIND=dp) else a(j,j) = real(a(j,j),KIND=dp) end if jx = jx + incx end do end if else ! form a when a is stored in lower triangle. if (incx==1) then do j = 1,n if (x(j)/=czero) then temp = alpha*conjg(x(j)) a(j,j) = real(a(j,j),KIND=dp) + real(temp*x(j),KIND=dp) do i = j + 1,n a(i,j) = a(i,j) + x(i)*temp end do else a(j,j) = real(a(j,j),KIND=dp) end if end do else jx = kx do j = 1,n if (x(jx)/=czero) then temp = alpha*conjg(x(jx)) a(j,j) = real(a(j,j),KIND=dp) + real(temp*x(jx),KIND=dp) ix = jx do i = j + 1,n ix = ix + incx a(i,j) = a(i,j) + x(ix)*temp end do else a(j,j) = real(a(j,j),KIND=dp) end if jx = jx + incx end do end if end if return end subroutine stdlib_zher