stdlib_dasum Function

public pure function stdlib_dasum(n, dx, incx)

DASUM takes the sum of the absolute values.

Arguments

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

Return Value real(kind=dp)


Source Code

     pure real(dp) function stdlib_dasum(n,dx,incx)
     !! DASUM takes the sum of the absolute values.
        ! -- 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, n
           ! Array Arguments 
           real(dp), intent(in) :: dx(*)
        ! =====================================================================
           ! Local Scalars 
           real(dp) :: dtemp
           integer(ilp) :: i, m, mp1, nincx
           ! Intrinsic Functions 
           intrinsic :: abs,mod
           stdlib_dasum = zero
           dtemp = zero
           if (n<=0 .or. incx<=0) return
           if (incx==1) then
              ! code for increment equal to 1
              ! clean-up loop
              m = mod(n,6)
              if (m/=0) then
                 do i = 1,m
                    dtemp = dtemp + abs(dx(i))
                 end do
                 if (n<6) then
                    stdlib_dasum = dtemp
                    return
                 end if
              end if
              mp1 = m + 1
              do i = mp1,n,6
                 dtemp = dtemp + abs(dx(i)) + abs(dx(i+1)) +abs(dx(i+2)) + abs(dx(i+3)) +abs(dx(i+&
                           4)) + abs(dx(i+5))
              end do
           else
              ! code for increment not equal to 1
              nincx = n*incx
              do i = 1,nincx,incx
                 dtemp = dtemp + abs(dx(i))
              end do
           end if
           stdlib_dasum = dtemp
           return
     end function stdlib_dasum