stdlib_drot Subroutine

public pure subroutine stdlib_drot(n, dx, incx, dy, incy, c, s)

DROT applies a plane rotation.

Arguments

Type IntentOptional 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
real(kind=dp), intent(in) :: c
real(kind=dp), intent(in) :: s

Source Code

     pure subroutine stdlib_drot(n,dx,incx,dy,incy,c,s)
     !! DROT applies a plane rotation.
        ! -- 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 
           real(dp), intent(in) :: c, s
           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
           if (n<=0) return
           if (incx==1 .and. incy==1) then
             ! code for both increments equal to 1
              do i = 1,n
                 dtemp = c*dx(i) + s*dy(i)
                 dy(i) = c*dy(i) - s*dx(i)
                 dx(i) = 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 = c*dx(ix) + s*dy(iy)
                 dy(iy) = c*dy(iy) - s*dx(ix)
                 dx(ix) = dtemp
                 ix = ix + incx
                 iy = iy + incy
              end do
           end if
           return
     end subroutine stdlib_drot