SDOT forms the dot product of two vectors. uses unrolled loops for increments equal to one.
Type | Intent | Optional | 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 |
pure real(sp) function stdlib_sdot(n,sx,incx,sy,incy) !! SDOT 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(sp), intent(in) :: sx(*), sy(*) ! ===================================================================== ! Local Scalars real(sp) :: stemp integer(ilp) :: i, ix, iy, m, mp1 ! Intrinsic Functions intrinsic :: mod stemp = zero stdlib_sdot = 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 stemp = stemp + sx(i)*sy(i) end do if (n<5) then stdlib_sdot=stemp return end if end if mp1 = m + 1 do i = mp1,n,5 stemp = stemp + sx(i)*sy(i) + sx(i+1)*sy(i+1) +sx(i+2)*sy(i+2) + sx(i+3)*sy(i+3) + & sx(i+4)*sy(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 stemp = stemp + sx(ix)*sy(iy) ix = ix + incx iy = iy + incy end do end if stdlib_sdot = stemp return end function stdlib_sdot