stdlib_zdrot Subroutine

public pure subroutine stdlib_zdrot(n, zx, incx, zy, incy, c, s)

Applies a plane rotation, where the cos and sin (c and s) are real and the vectors cx and cy are complex. jack dongarra, linpack, 3/11/78.

Arguments

Type IntentOptional Attributes Name
integer(kind=ilp), intent(in) :: n
complex(kind=dp), intent(inout) :: zx(*)
integer(kind=ilp), intent(in) :: incx
complex(kind=dp), intent(inout) :: zy(*)
integer(kind=ilp), intent(in) :: incy
real(kind=dp), intent(in) :: c
real(kind=dp), intent(in) :: s

Source Code

     pure subroutine stdlib_zdrot( n, zx, incx, zy, incy, c, s )
     !! Applies a plane rotation, where the cos and sin (c and s) are real
     !! and the vectors cx and cy are complex.
     !! jack dongarra, linpack, 3/11/78.
        ! -- 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
           real(dp), intent(in) :: c, s
           ! Array Arguments 
           complex(dp), intent(inout) :: zx(*), zy(*)
       ! =====================================================================
           ! Local Scalars 
           integer(ilp) :: i, ix, iy
           complex(dp) :: ctemp
           ! Executable Statements 
           if( n<=0 )return
           if( incx==1 .and. incy==1 ) then
              ! code for both increments equal to 1
              do i = 1, n
                 ctemp = c*zx( i ) + s*zy( i )
                 zy( i ) = c*zy( i ) - s*zx( i )
                 zx( i ) = ctemp
              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
                 ctemp = c*zx( ix ) + s*zy( iy )
                 zy( iy ) = c*zy( iy ) - s*zx( ix )
                 zx( ix ) = ctemp
                 ix = ix + incx
                 iy = iy + incy
              end do
           end if
           return
     end subroutine stdlib_zdrot