stdlib_ddot Function

public pure function stdlib_ddot(n, dx, incx, dy, incy)

DDOT forms the dot product of two vectors. uses unrolled loops for increments equal to one.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: n
real(kind=dp), intent(in) :: dx(*)
integer(kind=ilp), intent(in) :: incx
real(kind=dp), intent(in) :: dy(*)
integer(kind=ilp), intent(in) :: incy

Return Value real(kind=dp)


Source Code

     pure real(dp) function stdlib_ddot(n,dx,incx,dy,incy)
     !! DDOT forms the dot product of two vectors.
     !! uses unrolled loops for increments equal to one.
        ! -- 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 
           real(dp), intent(in) :: dx(*), dy(*)
        ! =====================================================================
           ! Local Scalars 
           real(dp) :: dtemp
           integer(ilp) :: i, ix, iy, m, mp1
           ! Intrinsic Functions 
           intrinsic :: mod
           stdlib_ddot = zero
           dtemp = zero
           if (n<=0) return
           if (incx==1 .and. incy==1) then
              ! code for both increments equal to 1
              ! clean-up loop
              m = mod(n,5)
              if (m/=0) then
                 do i = 1,m
                    dtemp = dtemp + dx(i)*dy(i)
                 end do
                 if (n<5) then
                    stdlib_ddot=dtemp
                 return
                 end if
              end if
              mp1 = m + 1
              do i = mp1,n,5
               dtemp = dtemp + dx(i)*dy(i) + dx(i+1)*dy(i+1) +dx(i+2)*dy(i+2) + dx(i+3)*dy(i+3) + &
                         dx(i+4)*dy(i+4)
              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
                 dtemp = dtemp + dx(ix)*dy(iy)
                 ix = ix + incx
                 iy = iy + incy
              end do
           end if
           stdlib_ddot = dtemp
           return
     end function stdlib_ddot