File:  [local] / rpl / lapack / lapack / zrot.f
Revision 1.1: download - view: text, annotated - select for diffs - revision graph
Tue Jan 26 15:22:46 2010 UTC (14 years, 3 months ago) by bertrand
Branches: MAIN
CVS tags: HEAD
Initial revision

    1:       SUBROUTINE ZROT( N, CX, INCX, CY, INCY, C, S )
    2: *
    3: *  -- LAPACK auxiliary routine (version 3.2) --
    4: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
    5: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
    6: *     November 2006
    7: *
    8: *     .. Scalar Arguments ..
    9:       INTEGER            INCX, INCY, N
   10:       DOUBLE PRECISION   C
   11:       COMPLEX*16         S
   12: *     ..
   13: *     .. Array Arguments ..
   14:       COMPLEX*16         CX( * ), CY( * )
   15: *     ..
   16: *
   17: *  Purpose
   18: *  =======
   19: *
   20: *  ZROT   applies a plane rotation, where the cos (C) is real and the
   21: *  sin (S) is complex, and the vectors CX and CY are complex.
   22: *
   23: *  Arguments
   24: *  =========
   25: *
   26: *  N       (input) INTEGER
   27: *          The number of elements in the vectors CX and CY.
   28: *
   29: *  CX      (input/output) COMPLEX*16 array, dimension (N)
   30: *          On input, the vector X.
   31: *          On output, CX is overwritten with C*X + S*Y.
   32: *
   33: *  INCX    (input) INTEGER
   34: *          The increment between successive values of CY.  INCX <> 0.
   35: *
   36: *  CY      (input/output) COMPLEX*16 array, dimension (N)
   37: *          On input, the vector Y.
   38: *          On output, CY is overwritten with -CONJG(S)*X + C*Y.
   39: *
   40: *  INCY    (input) INTEGER
   41: *          The increment between successive values of CY.  INCX <> 0.
   42: *
   43: *  C       (input) DOUBLE PRECISION
   44: *  S       (input) COMPLEX*16
   45: *          C and S define a rotation
   46: *             [  C          S  ]
   47: *             [ -conjg(S)   C  ]
   48: *          where C*C + S*CONJG(S) = 1.0.
   49: *
   50: * =====================================================================
   51: *
   52: *     .. Local Scalars ..
   53:       INTEGER            I, IX, IY
   54:       COMPLEX*16         STEMP
   55: *     ..
   56: *     .. Intrinsic Functions ..
   57:       INTRINSIC          DCONJG
   58: *     ..
   59: *     .. Executable Statements ..
   60: *
   61:       IF( N.LE.0 )
   62:      $   RETURN
   63:       IF( INCX.EQ.1 .AND. INCY.EQ.1 )
   64:      $   GO TO 20
   65: *
   66: *     Code for unequal increments or equal increments not equal to 1
   67: *
   68:       IX = 1
   69:       IY = 1
   70:       IF( INCX.LT.0 )
   71:      $   IX = ( -N+1 )*INCX + 1
   72:       IF( INCY.LT.0 )
   73:      $   IY = ( -N+1 )*INCY + 1
   74:       DO 10 I = 1, N
   75:          STEMP = C*CX( IX ) + S*CY( IY )
   76:          CY( IY ) = C*CY( IY ) - DCONJG( S )*CX( IX )
   77:          CX( IX ) = STEMP
   78:          IX = IX + INCX
   79:          IY = IY + INCY
   80:    10 CONTINUE
   81:       RETURN
   82: *
   83: *     Code for both increments equal to 1
   84: *
   85:    20 CONTINUE
   86:       DO 30 I = 1, N
   87:          STEMP = C*CX( I ) + S*CY( I )
   88:          CY( I ) = C*CY( I ) - DCONJG( S )*CX( I )
   89:          CX( I ) = STEMP
   90:    30 CONTINUE
   91:       RETURN
   92:       END

CVSweb interface <joel.bertrand@systella.fr>