File:  [local] / rpl / lapack / blas / zgeru.f
Revision 1.16: download - view: text, annotated - select for diffs - revision graph
Mon Aug 7 08:38:45 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 ZGERU
    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 ZGERU(M,N,ALPHA,X,INCX,Y,INCY,A,LDA)
   12: *
   13: *       .. Scalar Arguments ..
   14: *       COMPLEX*16 ALPHA
   15: *       INTEGER INCX,INCY,LDA,M,N
   16: *       ..
   17: *       .. Array Arguments ..
   18: *       COMPLEX*16 A(LDA,*),X(*),Y(*)
   19: *       ..
   20: *
   21: *
   22: *> \par Purpose:
   23: *  =============
   24: *>
   25: *> \verbatim
   26: *>
   27: *> ZGERU  performs the rank 1 operation
   28: *>
   29: *>    A := alpha*x*y**T + A,
   30: *>
   31: *> where alpha is a scalar, x is an m element vector, y is an n element
   32: *> vector and A is an m by n matrix.
   33: *> \endverbatim
   34: *
   35: *  Arguments:
   36: *  ==========
   37: *
   38: *> \param[in] M
   39: *> \verbatim
   40: *>          M is INTEGER
   41: *>           On entry, M specifies the number of rows of the matrix A.
   42: *>           M must be at least zero.
   43: *> \endverbatim
   44: *>
   45: *> \param[in] N
   46: *> \verbatim
   47: *>          N is INTEGER
   48: *>           On entry, N specifies the number of columns of the matrix A.
   49: *>           N must be at least zero.
   50: *> \endverbatim
   51: *>
   52: *> \param[in] ALPHA
   53: *> \verbatim
   54: *>          ALPHA is COMPLEX*16
   55: *>           On entry, ALPHA specifies the scalar alpha.
   56: *> \endverbatim
   57: *>
   58: *> \param[in] X
   59: *> \verbatim
   60: *>          X is COMPLEX*16 array, dimension at least
   61: *>           ( 1 + ( m - 1 )*abs( INCX ) ).
   62: *>           Before entry, the incremented array X must contain the m
   63: *>           element vector x.
   64: *> \endverbatim
   65: *>
   66: *> \param[in] INCX
   67: *> \verbatim
   68: *>          INCX is INTEGER
   69: *>           On entry, INCX specifies the increment for the elements of
   70: *>           X. INCX must not be zero.
   71: *> \endverbatim
   72: *>
   73: *> \param[in] Y
   74: *> \verbatim
   75: *>          Y is COMPLEX*16 array, dimension at least
   76: *>           ( 1 + ( n - 1 )*abs( INCY ) ).
   77: *>           Before entry, the incremented array Y must contain the n
   78: *>           element vector y.
   79: *> \endverbatim
   80: *>
   81: *> \param[in] INCY
   82: *> \verbatim
   83: *>          INCY is INTEGER
   84: *>           On entry, INCY specifies the increment for the elements of
   85: *>           Y. INCY must not be zero.
   86: *> \endverbatim
   87: *>
   88: *> \param[in,out] A
   89: *> \verbatim
   90: *>          A is COMPLEX*16 array, dimension ( LDA, N )
   91: *>           Before entry, the leading m by n part of the array A must
   92: *>           contain the matrix of coefficients. On exit, A is
   93: *>           overwritten by the updated matrix.
   94: *> \endverbatim
   95: *>
   96: *> \param[in] LDA
   97: *> \verbatim
   98: *>          LDA is INTEGER
   99: *>           On entry, LDA specifies the first dimension of A as declared
  100: *>           in the calling (sub) program. LDA must be at least
  101: *>           max( 1, m ).
  102: *> \endverbatim
  103: *
  104: *  Authors:
  105: *  ========
  106: *
  107: *> \author Univ. of Tennessee
  108: *> \author Univ. of California Berkeley
  109: *> \author Univ. of Colorado Denver
  110: *> \author NAG Ltd.
  111: *
  112: *> \ingroup complex16_blas_level2
  113: *
  114: *> \par Further Details:
  115: *  =====================
  116: *>
  117: *> \verbatim
  118: *>
  119: *>  Level 2 Blas routine.
  120: *>
  121: *>  -- Written on 22-October-1986.
  122: *>     Jack Dongarra, Argonne National Lab.
  123: *>     Jeremy Du Croz, Nag Central Office.
  124: *>     Sven Hammarling, Nag Central Office.
  125: *>     Richard Hanson, Sandia National Labs.
  126: *> \endverbatim
  127: *>
  128: *  =====================================================================
  129:       SUBROUTINE ZGERU(M,N,ALPHA,X,INCX,Y,INCY,A,LDA)
  130: *
  131: *  -- Reference BLAS level2 routine --
  132: *  -- Reference BLAS is a software package provided by Univ. of Tennessee,    --
  133: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  134: *
  135: *     .. Scalar Arguments ..
  136:       COMPLEX*16 ALPHA
  137:       INTEGER INCX,INCY,LDA,M,N
  138: *     ..
  139: *     .. Array Arguments ..
  140:       COMPLEX*16 A(LDA,*),X(*),Y(*)
  141: *     ..
  142: *
  143: *  =====================================================================
  144: *
  145: *     .. Parameters ..
  146:       COMPLEX*16 ZERO
  147:       PARAMETER (ZERO= (0.0D+0,0.0D+0))
  148: *     ..
  149: *     .. Local Scalars ..
  150:       COMPLEX*16 TEMP
  151:       INTEGER I,INFO,IX,J,JY,KX
  152: *     ..
  153: *     .. External Subroutines ..
  154:       EXTERNAL XERBLA
  155: *     ..
  156: *     .. Intrinsic Functions ..
  157:       INTRINSIC MAX
  158: *     ..
  159: *
  160: *     Test the input parameters.
  161: *
  162:       INFO = 0
  163:       IF (M.LT.0) THEN
  164:           INFO = 1
  165:       ELSE IF (N.LT.0) THEN
  166:           INFO = 2
  167:       ELSE IF (INCX.EQ.0) THEN
  168:           INFO = 5
  169:       ELSE IF (INCY.EQ.0) THEN
  170:           INFO = 7
  171:       ELSE IF (LDA.LT.MAX(1,M)) THEN
  172:           INFO = 9
  173:       END IF
  174:       IF (INFO.NE.0) THEN
  175:           CALL XERBLA('ZGERU ',INFO)
  176:           RETURN
  177:       END IF
  178: *
  179: *     Quick return if possible.
  180: *
  181:       IF ((M.EQ.0) .OR. (N.EQ.0) .OR. (ALPHA.EQ.ZERO)) RETURN
  182: *
  183: *     Start the operations. In this version the elements of A are
  184: *     accessed sequentially with one pass through A.
  185: *
  186:       IF (INCY.GT.0) THEN
  187:           JY = 1
  188:       ELSE
  189:           JY = 1 - (N-1)*INCY
  190:       END IF
  191:       IF (INCX.EQ.1) THEN
  192:           DO 20 J = 1,N
  193:               IF (Y(JY).NE.ZERO) THEN
  194:                   TEMP = ALPHA*Y(JY)
  195:                   DO 10 I = 1,M
  196:                       A(I,J) = A(I,J) + X(I)*TEMP
  197:    10             CONTINUE
  198:               END IF
  199:               JY = JY + INCY
  200:    20     CONTINUE
  201:       ELSE
  202:           IF (INCX.GT.0) THEN
  203:               KX = 1
  204:           ELSE
  205:               KX = 1 - (M-1)*INCX
  206:           END IF
  207:           DO 40 J = 1,N
  208:               IF (Y(JY).NE.ZERO) THEN
  209:                   TEMP = ALPHA*Y(JY)
  210:                   IX = KX
  211:                   DO 30 I = 1,M
  212:                       A(I,J) = A(I,J) + X(IX)*TEMP
  213:                       IX = IX + INCX
  214:    30             CONTINUE
  215:               END IF
  216:               JY = JY + INCY
  217:    40     CONTINUE
  218:       END IF
  219: *
  220:       RETURN
  221: *
  222: *     End of ZGERU
  223: *
  224:       END

CVSweb interface <joel.bertrand@systella.fr>