File:  [local] / rpl / lapack / blas / zaxpy.f
Revision 1.16: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:38:44 2023 UTC (8 months, 3 weeks ago) by bertrand
Branches: MAIN
CVS tags: rpl-4_1_35, rpl-4_1_34, HEAD
Première mise à jour de lapack et blas.

    1: *> \brief \b ZAXPY
    2: *
    3: *  =========== DOCUMENTATION ===========
    4: *
    5: * Online html documentation available at
    6: *            http://www.netlib.org/lapack/explore-html/
    7: *
    8: *  Definition:
    9: *  ===========
   10: *
   11: *       SUBROUTINE ZAXPY(N,ZA,ZX,INCX,ZY,INCY)
   12: *
   13: *       .. Scalar Arguments ..
   14: *       COMPLEX*16 ZA
   15: *       INTEGER INCX,INCY,N
   16: *       ..
   17: *       .. Array Arguments ..
   18: *       COMPLEX*16 ZX(*),ZY(*)
   19: *       ..
   20: *
   21: *
   22: *> \par Purpose:
   23: *  =============
   24: *>
   25: *> \verbatim
   26: *>
   27: *>    ZAXPY constant times a vector plus a vector.
   28: *> \endverbatim
   29: *
   30: *  Arguments:
   31: *  ==========
   32: *
   33: *> \param[in] N
   34: *> \verbatim
   35: *>          N is INTEGER
   36: *>         number of elements in input vector(s)
   37: *> \endverbatim
   38: *>
   39: *> \param[in] ZA
   40: *> \verbatim
   41: *>          ZA is COMPLEX*16
   42: *>           On entry, ZA specifies the scalar alpha.
   43: *> \endverbatim
   44: *>
   45: *> \param[in] ZX
   46: *> \verbatim
   47: *>          ZX is COMPLEX*16 array, dimension ( 1 + ( N - 1 )*abs( INCX ) )
   48: *> \endverbatim
   49: *>
   50: *> \param[in] INCX
   51: *> \verbatim
   52: *>          INCX is INTEGER
   53: *>         storage spacing between elements of ZX
   54: *> \endverbatim
   55: *>
   56: *> \param[in,out] ZY
   57: *> \verbatim
   58: *>          ZY is COMPLEX*16 array, dimension ( 1 + ( N - 1 )*abs( INCY ) )
   59: *> \endverbatim
   60: *>
   61: *> \param[in] INCY
   62: *> \verbatim
   63: *>          INCY is INTEGER
   64: *>         storage spacing between elements of ZY
   65: *> \endverbatim
   66: *
   67: *  Authors:
   68: *  ========
   69: *
   70: *> \author Univ. of Tennessee
   71: *> \author Univ. of California Berkeley
   72: *> \author Univ. of Colorado Denver
   73: *> \author NAG Ltd.
   74: *
   75: *> \ingroup complex16_blas_level1
   76: *
   77: *> \par Further Details:
   78: *  =====================
   79: *>
   80: *> \verbatim
   81: *>
   82: *>     jack dongarra, 3/11/78.
   83: *>     modified 12/3/93, array(1) declarations changed to array(*)
   84: *> \endverbatim
   85: *>
   86: *  =====================================================================
   87:       SUBROUTINE ZAXPY(N,ZA,ZX,INCX,ZY,INCY)
   88: *
   89: *  -- Reference BLAS level1 routine --
   90: *  -- Reference BLAS is a software package provided by Univ. of Tennessee,    --
   91: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
   92: *
   93: *     .. Scalar Arguments ..
   94:       COMPLEX*16 ZA
   95:       INTEGER INCX,INCY,N
   96: *     ..
   97: *     .. Array Arguments ..
   98:       COMPLEX*16 ZX(*),ZY(*)
   99: *     ..
  100: *
  101: *  =====================================================================
  102: *
  103: *     .. Local Scalars ..
  104:       INTEGER I,IX,IY
  105: *     ..
  106: *     .. External Functions ..
  107:       DOUBLE PRECISION DCABS1
  108:       EXTERNAL DCABS1
  109: *     ..
  110:       IF (N.LE.0) RETURN
  111:       IF (DCABS1(ZA).EQ.0.0d0) RETURN
  112:       IF (INCX.EQ.1 .AND. INCY.EQ.1) THEN
  113: *
  114: *        code for both increments equal to 1
  115: *
  116:          DO I = 1,N
  117:             ZY(I) = ZY(I) + ZA*ZX(I)
  118:          END DO
  119:       ELSE
  120: *
  121: *        code for unequal increments or equal increments
  122: *          not equal to 1
  123: *
  124:          IX = 1
  125:          IY = 1
  126:          IF (INCX.LT.0) IX = (-N+1)*INCX + 1
  127:          IF (INCY.LT.0) IY = (-N+1)*INCY + 1
  128:          DO I = 1,N
  129:             ZY(IY) = ZY(IY) + ZA*ZX(IX)
  130:             IX = IX + INCX
  131:             IY = IY + INCY
  132:          END DO
  133:       END IF
  134: *
  135:       RETURN
  136: *
  137: *     End of ZAXPY
  138: *
  139:       END

CVSweb interface <joel.bertrand@systella.fr>