DSWAP interchanges two vectors. uses unrolled loops for increments equal to 1.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
real(kind=dp), | intent(inout) | :: | dx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
real(kind=dp), | intent(inout) | :: | dy(*) | |||
integer(kind=ilp), | intent(in) | :: | incy |
pure subroutine stdlib_dswap(n,dx,incx,dy,incy) !! DSWAP interchanges two vectors. !! uses unrolled loops for increments equal to 1. ! -- 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(inout) :: dx(*), dy(*) ! ===================================================================== ! Local Scalars real(dp) :: dtemp integer(ilp) :: i, ix, iy, m, mp1 ! Intrinsic Functions intrinsic :: mod if (n<=0) return if (incx==1 .and. incy==1) then ! code for both increments equal to 1 ! clean-up loop m = mod(n,3) if (m/=0) then do i = 1,m dtemp = dx(i) dx(i) = dy(i) dy(i) = dtemp end do if (n<3) return end if mp1 = m + 1 do i = mp1,n,3 dtemp = dx(i) dx(i) = dy(i) dy(i) = dtemp dtemp = dx(i+1) dx(i+1) = dy(i+1) dy(i+1) = dtemp dtemp = dx(i+2) dx(i+2) = dy(i+2) dy(i+2) = dtemp 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 = dx(ix) dx(ix) = dy(iy) dy(iy) = dtemp ix = ix + incx iy = iy + incy end do end if return end subroutine stdlib_dswap