stdlib_scasum Function

public pure function stdlib_scasum(n, cx, incx)

SCASUM takes the sum of the (|Re(.)| + |Im(.)|)'s of a complex vector and returns a single precision result.

Arguments

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

Return Value real(kind=sp)


Source Code

     pure real(sp) function stdlib_scasum(n,cx,incx)
     !! SCASUM takes the sum of the (|Re(.)| + |Im(.)|)'s of a complex vector and
     !! returns a single precision result.
        ! -- 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 
           complex(sp), intent(in) :: cx(*)
        ! =====================================================================
           ! Local Scalars 
           real(sp) :: stemp
           integer(ilp) :: i, nincx
           ! Intrinsic Functions 
           intrinsic :: abs,aimag,real
           stdlib_scasum = zero
           stemp = zero
           if (n<=0 .or. incx<=0) return
           if (incx==1) then
              ! code for increment equal to 1
              do i = 1,n
                 stemp = stemp + abs(real(cx(i),KIND=sp)) + abs(aimag(cx(i)))
              end do
           else
              ! code for increment not equal to 1
              nincx = n*incx
              do i = 1,nincx,incx
                 stemp = stemp + abs(real(cx(i),KIND=sp)) + abs(aimag(cx(i)))
              end do
           end if
           stdlib_scasum = stemp
           return
     end function stdlib_scasum