stdlib_cdotu Function

public pure function stdlib_cdotu(n, cx, incx, cy, incy)

CDOTU forms the dot product of two complex vectors CDOTU = X^T * Y

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: n
complex(kind=sp), intent(in) :: cx(*)
integer(kind=ilp), intent(in) :: incx
complex(kind=sp), intent(in) :: cy(*)
integer(kind=ilp), intent(in) :: incy

Return Value complex(kind=sp)


Source Code

     pure complex(sp) function stdlib_cdotu(n,cx,incx,cy,incy)
     !! CDOTU forms the dot product of two complex vectors
     !! CDOTU = X^T * Y
        ! -- 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 
           integer(ilp), intent(in) :: incx, incy, n
           ! Array Arguments 
           complex(sp), intent(in) :: cx(*), cy(*)
        ! =====================================================================
           ! Local Scalars 
           complex(sp) :: ctemp
           integer(ilp) :: i, ix, iy
           ctemp = (0.0_sp,0.0_sp)
           stdlib_cdotu = (0.0_sp,0.0_sp)
           if (n<=0) return
           if (incx==1 .and. incy==1) then
              ! code for both increments equal to 1
              do i = 1,n
                 ctemp = ctemp + cx(i)*cy(i)
              end do
           else
              ! code for unequal increments or equal increments
                ! not equal to 1
              ix = 1
              iy = 1
              if (incx<0) ix = (-n+1)*incx + 1
              if (incy<0) iy = (-n+1)*incy + 1
              do i = 1,n
                 ctemp = ctemp + cx(ix)*cy(iy)
                 ix = ix + incx
                 iy = iy + incy
              end do
           end if
           stdlib_cdotu = ctemp
           return
     end function stdlib_cdotu