applies a plane rotation.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | n | |||
real(kind=sp), | intent(inout) | :: | sx(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
real(kind=sp), | intent(inout) | :: | sy(*) | |||
integer(kind=ilp), | intent(in) | :: | incy | |||
real(kind=sp), | intent(in) | :: | c | |||
real(kind=sp), | intent(in) | :: | s |
pure subroutine stdlib_srot(n,sx,incx,sy,incy,c,s) !! 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(sp), intent(in) :: c, s integer(ilp), intent(in) :: incx, incy, n ! Array Arguments real(sp), intent(inout) :: sx(*), sy(*) ! ===================================================================== ! Local Scalars real(sp) :: stemp 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 stemp = c*sx(i) + s*sy(i) sy(i) = c*sy(i) - s*sx(i) sx(i) = stemp 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 = c*sx(ix) + s*sy(iy) sy(iy) = c*sy(iy) - s*sx(ix) sx(ix) = stemp ix = ix + incx iy = iy + incy end do end if return end subroutine stdlib_srot