stdlib_dsdot Function

public pure function stdlib_dsdot(n, sx, incx, sy, incy)

Compute the inner product of two vectors with extended precision accumulation and result. Returns D.P. dot product accumulated in D.P., for S.P. SX and SY DSDOT = sum for I = 0 to N-1 of SX(LX+IINCX) * SY(LY+IINCY), where LX = 1 if INCX >= 0, else LX = 1+(1-N)*INCX, and LY is defined in a similar way using INCY.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: n
real(kind=sp), intent(in) :: sx(*)
integer(kind=ilp), intent(in) :: incx
real(kind=sp), intent(in) :: sy(*)
integer(kind=ilp), intent(in) :: incy

Return Value real(kind=dp)


Source Code

     pure real(dp) function stdlib_dsdot(n,sx,incx,sy,incy)
     !! Compute the inner product of two vectors with extended
     !! precision accumulation and result.
     !! Returns D.P. dot product accumulated in D.P., for S.P. SX and SY
     !! DSDOT = sum for I = 0 to N-1 of  SX(LX+I*INCX) * SY(LY+I*INCY),
     !! where LX = 1 if INCX >= 0, else LX = 1+(1-N)*INCX, and LY is
     !! defined in a similar way using INCY.
        ! -- 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(sp), intent(in) :: sx(*), sy(*)
        ! authors:
        ! ========
        ! lawson, c. l., (jpl), hanson, r. j., (snla),
        ! kincaid, d. r., (u. of texas), krogh, f. t., (jpl)
        ! =====================================================================
           ! Local Scalars 
           integer(ilp) :: i, kx, ky, ns
           ! Intrinsic Functions 
           intrinsic :: real
           stdlib_dsdot = zero
           if (n<=0) return
           if (incx==incy .and. incx>0) then
           ! code for equal, positive, non-unit increments.
              ns = n*incx
              do i = 1,ns,incx
                 stdlib_dsdot = stdlib_dsdot + real(sx(i),KIND=dp)*real(sy(i),KIND=dp)
              end do
           else
           ! code for unequal or nonpositive increments.
              kx = 1
              ky = 1
              if (incx<0) kx = 1 + (1-n)*incx
              if (incy<0) ky = 1 + (1-n)*incy
              do i = 1,n
                 stdlib_dsdot = stdlib_dsdot + real(sx(kx),KIND=dp)*real(sy(ky),KIND=dp)
                 kx = kx + incx
                 ky = ky + incy
              end do
           end if
           return
     end function stdlib_dsdot