Contents
     daxpyi - Compute y := alpha * x + y
      SUBROUTINE DAXPYI(NZ, A, X, INDX, Y)
      DOUBLE PRECISION A
      DOUBLE PRECISION X(*), Y(*)
      INTEGER NZ
      INTEGER INDX(*)
      SUBROUTINE DAXPYI_64(NZ, A, X, INDX, Y)
      DOUBLE PRECISION A
      DOUBLE PRECISION X(*), Y(*)
      INTEGER*8 NZ
      INTEGER*8 INDX(*)
     F95 INTERFACE
      SUBROUTINE AXPYI([NZ], [A], X, INDX, Y)
      REAL(8) :: A
      REAL(8), DIMENSION(:) :: X, Y
      INTEGER :: NZ
      INTEGER, DIMENSION(:) :: INDX
      SUBROUTINE AXPYI_64([NZ], [A], X, INDX, Y)
      REAL(8) :: A
      REAL(8), DIMENSION(:) :: X, Y
      INTEGER(8) :: NZ
      INTEGER(8), DIMENSION(:) :: INDX
     DAXPYI Compute y := alpha * x + y where alpha is a scalar, x
     is a sparse vector, and y is a vector in full storage form
      do i = 1, n
        y(indx(i)) = alpha * x(i) + y(indx(i))
      enddo
     NZ (input) - INTEGER
             Number of elements in the compressed form.
             Unchanged on exit.
     A (input)
             On entry, A(LPHA) specifies the scaling value.
             Unchanged on exit.  A is defaulted to 1.0D0 for F95
             INTERFACE.
     X (input)
             Vector containing the values of the compressed form.
             Unchanged on exit.
     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 (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.