stdlib_zdscal Subroutine

public pure subroutine stdlib_zdscal(n, da, zx, incx)

ZDSCAL scales a vector by a constant.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: n
real(kind=dp), intent(in) :: da
complex(kind=dp), intent(inout) :: zx(*)
integer(kind=ilp), intent(in) :: incx

Source Code

     pure subroutine stdlib_zdscal(n,da,zx,incx)
     !! ZDSCAL scales a vector by a constant.
        ! -- reference blas level1 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) :: da
           integer(ilp), intent(in) :: incx, n
           ! Array Arguments 
           complex(dp), intent(inout) :: zx(*)
        ! =====================================================================
           ! Local Scalars 
           integer(ilp) :: i, nincx
           ! Intrinsic Functions 
           intrinsic :: cmplx
           if (n<=0 .or. incx<=0) return
           if (incx==1) then
              ! code for increment equal to 1
              do i = 1,n
                 zx(i) = cmplx(da,0.0_dp,KIND=dp)*zx(i)
              end do
           else
              ! code for increment not equal to 1
              nincx = n*incx
              do i = 1,nincx,incx
                 zx(i) = cmplx(da,0.0_dp,KIND=dp)*zx(i)
              end do
           end if
           return
     end subroutine stdlib_zdscal