Contents


NAME

     droti -  Apply an indexed Givens rotation.

SYNOPSIS

      SUBROUTINE DROTI(NZ, X, INDX, Y, C, S)

      INTEGER NZ
      INTEGER INDX(*)
      DOUBLE PRECISION C, S
      DOUBLE PRECISION X(*), Y(*)

      SUBROUTINE DROTI_64(NZ, X, INDX, Y, C, S)

      INTEGER*8 NZ
      INTEGER*8 INDX(*)
      DOUBLE PRECISION C, S
      DOUBLE PRECISION X(*), Y(*)

     F95 INTERFACE
      SUBROUTINE ROTI([NZ], X, INDX, Y, C, S)

      INTEGER :: NZ
      INTEGER, DIMENSION(:) :: INDX
      REAL(8) :: C, S
      REAL(8), DIMENSION(:) :: X, Y

      SUBROUTINE ROTI_64([NZ], X, INDX, Y, C, S)

      INTEGER(8) :: NZ
      INTEGER(8), DIMENSION(:) :: INDX
      REAL(8) :: C, S
      REAL(8), DIMENSION(:) :: X, Y

PURPOSE

     DROTI - Applies a Givens rotation to a sparse vector x
     stored in compressed form and another vector y in full
     storage form

      do i = 1, n
        temp = -s * x(i) + c * y(indx(i))
        x(i) = c * x(i) + s * y(indx(i))
        y(indx(i)) = temp
      enddo

ARGUMENTS

     NZ (input) - INTEGER
             Number of elements in the compressed form.
             Unchanged on exit.
     X (input)
             Vector containing the values of the compressed form.

     INDX (input) - INTEGER
             Vector containing the indices of the compressed
             form.  It is assumed that the elements in INDX are
             distinct and greater than zero.  Unchanged on exit.

     Y (input/output)
             Vector on input which contains the vector Y in full
             storage form.  On exit, only the elements
             corresponding to the indices in INDX have been
             modified.

     C (input)
             Scalar defining the Givens rotation

     S (input)
             Scalar defining the Givens rotation