ZHPR2 performs the hermitian rank 2 operation A := alphaxyH + conjg( alpha )yxH + A, where alpha is a scalar, x and y are n element vectors and A is an n by n hermitian matrix, supplied in packed form.
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) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=dp), | intent(in) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy | |||
complex(kind=dp), | intent(inout) | :: | ap(*) |
pure subroutine stdlib_zhpr2(uplo,n,alpha,x,incx,y,incy,ap) !! ZHPR2 performs the hermitian rank 2 operation !! A := alpha*x*y**H + conjg( alpha )*y*x**H + A, !! where alpha is a scalar, x and y are n element vectors and A is an !! n by n hermitian matrix, supplied in packed form. ! -- 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 integer(ilp), intent(in) :: incx, incy, n character, intent(in) :: uplo ! Array Arguments complex(dp), intent(inout) :: ap(*) complex(dp), intent(in) :: x(*), y(*) ! ===================================================================== ! Local Scalars complex(dp) :: temp1, temp2 integer(ilp) :: i, info, ix, iy, j, jx, jy, k, kk, kx, ky ! Intrinsic Functions intrinsic :: real,conjg ! 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 (incy==0) then info = 7 end if if (info/=0) then call stdlib_xerbla('ZHPR2 ',info) return end if ! quick return if possible. if ((n==0) .or. (alpha==czero)) return ! set up the start points in x and y if the increments are not both ! unity. if ((incx/=1) .or. (incy/=1)) then 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 jx = kx jy = ky end if ! start the operations. in this version the elements of the array ap ! are accessed sequentially with cone pass through ap. kk = 1 if (stdlib_lsame(uplo,'U')) then ! form a when upper triangle is stored in ap. if ((incx==1) .and. (incy==1)) then do j = 1,n if ((x(j)/=czero) .or. (y(j)/=czero)) then temp1 = alpha*conjg(y(j)) temp2 = conjg(alpha*x(j)) k = kk do i = 1,j - 1 ap(k) = ap(k) + x(i)*temp1 + y(i)*temp2 k = k + 1 end do ap(kk+j-1) = real(ap(kk+j-1),KIND=dp) +real(x(j)*temp1+y(j)*temp2,& KIND=dp) else ap(kk+j-1) = real(ap(kk+j-1),KIND=dp) end if kk = kk + j end do else do j = 1,n if ((x(jx)/=czero) .or. (y(jy)/=czero)) then temp1 = alpha*conjg(y(jy)) temp2 = conjg(alpha*x(jx)) ix = kx iy = ky do k = kk,kk + j - 2 ap(k) = ap(k) + x(ix)*temp1 + y(iy)*temp2 ix = ix + incx iy = iy + incy end do ap(kk+j-1) = real(ap(kk+j-1),KIND=dp) +real(x(jx)*temp1+y(jy)*temp2,& KIND=dp) else ap(kk+j-1) = real(ap(kk+j-1),KIND=dp) end if jx = jx + incx jy = jy + incy kk = kk + j end do end if else ! form a when lower triangle is stored in ap. if ((incx==1) .and. (incy==1)) then do j = 1,n if ((x(j)/=czero) .or. (y(j)/=czero)) then temp1 = alpha*conjg(y(j)) temp2 = conjg(alpha*x(j)) ap(kk) = real(ap(kk),KIND=dp) +real(x(j)*temp1+y(j)*temp2,KIND=dp) k = kk + 1 do i = j + 1,n ap(k) = ap(k) + x(i)*temp1 + y(i)*temp2 k = k + 1 end do else ap(kk) = real(ap(kk),KIND=dp) end if kk = kk + n - j + 1 end do else do j = 1,n if ((x(jx)/=czero) .or. (y(jy)/=czero)) then temp1 = alpha*conjg(y(jy)) temp2 = conjg(alpha*x(jx)) ap(kk) = real(ap(kk),KIND=dp) +real(x(jx)*temp1+y(jy)*temp2,KIND=dp) ix = jx iy = jy do k = kk + 1,kk + n - j ix = ix + incx iy = iy + incy ap(k) = ap(k) + x(ix)*temp1 + y(iy)*temp2 end do else ap(kk) = real(ap(kk),KIND=dp) end if jx = jx + incx jy = jy + incy kk = kk + n - j + 1 end do end if end if return end subroutine stdlib_zhpr2