Diff for /rpl/lapack/lapack/zla_geamv.f between versions 1.5 and 1.6

version 1.5, 2011/07/22 07:38:16 version 1.6, 2011/11/21 20:43:13
Line 1 Line 1
   *> \brief \b ZLA_GEAMV
   *
   *  =========== DOCUMENTATION ===========
   *
   * Online html documentation available at 
   *            http://www.netlib.org/lapack/explore-html/ 
   *
   *> \htmlonly
   *> Download ZLA_GEAMV + dependencies 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zla_geamv.f"> 
   *> [TGZ]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zla_geamv.f"> 
   *> [ZIP]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zla_geamv.f"> 
   *> [TXT]</a>
   *> \endhtmlonly 
   *
   *  Definition:
   *  ===========
   *
   *       SUBROUTINE ZLA_GEAMV ( TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA,
   *                              Y, INCY )
   * 
   *       .. Scalar Arguments ..
   *       DOUBLE PRECISION   ALPHA, BETA
   *       INTEGER            INCX, INCY, LDA, M, N
   *       INTEGER            TRANS
   *       ..
   *       .. Array Arguments ..
   *       COMPLEX*16         A( LDA, * ), X( * )
   *       DOUBLE PRECISION   Y( * )
   *       ..
   *  
   *
   *> \par Purpose:
   *  =============
   *>
   *> \verbatim
   *>
   *> ZLA_GEAMV  performs one of the matrix-vector operations
   *>
   *>         y := alpha*abs(A)*abs(x) + beta*abs(y),
   *>    or   y := alpha*abs(A)**T*abs(x) + beta*abs(y),
   *>
   *> where alpha and beta are scalars, x and y are vectors and A is an
   *> m by n matrix.
   *>
   *> This function is primarily used in calculating error bounds.
   *> To protect against underflow during evaluation, components in
   *> the resulting vector are perturbed away from zero by (N+1)
   *> times the underflow threshold.  To prevent unnecessarily large
   *> errors for block-structure embedded in general matrices,
   *> "symbolically" zero components are not perturbed.  A zero
   *> entry is considered "symbolic" if all multiplications involved
   *> in computing that entry have at least one zero multiplicand.
   *> \endverbatim
   *
   *  Arguments:
   *  ==========
   *
   *> \param[in] TRANS
   *> \verbatim
   *>          TRANS is INTEGER
   *>           On entry, TRANS specifies the operation to be performed as
   *>           follows:
   *>
   *>             BLAS_NO_TRANS      y := alpha*abs(A)*abs(x) + beta*abs(y)
   *>             BLAS_TRANS         y := alpha*abs(A**T)*abs(x) + beta*abs(y)
   *>             BLAS_CONJ_TRANS    y := alpha*abs(A**T)*abs(x) + beta*abs(y)
   *>
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in] M
   *> \verbatim
   *>          M is INTEGER
   *>           On entry, M specifies the number of rows of the matrix A.
   *>           M must be at least zero.
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in] N
   *> \verbatim
   *>          N is INTEGER
   *>           On entry, N specifies the number of columns of the matrix A.
   *>           N must be at least zero.
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in] ALPHA
   *> \verbatim
   *>          ALPHA is DOUBLE PRECISION
   *>           On entry, ALPHA specifies the scalar alpha.
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in] A
   *> \verbatim
   *>          A is COMPLEX*16 array of DIMENSION ( LDA, n )
   *>           Before entry, the leading m by n part of the array A must
   *>           contain the matrix of coefficients.
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in] LDA
   *> \verbatim
   *>          LDA is INTEGER
   *>           On entry, LDA specifies the first dimension of A as declared
   *>           in the calling (sub) program. LDA must be at least
   *>           max( 1, m ).
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in] X
   *> \verbatim
   *>          X is COMPLEX*16 array of DIMENSION at least
   *>           ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'
   *>           and at least
   *>           ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.
   *>           Before entry, the incremented array X must contain the
   *>           vector x.
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in] INCX
   *> \verbatim
   *>          INCX is INTEGER
   *>           On entry, INCX specifies the increment for the elements of
   *>           X. INCX must not be zero.
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in] BETA
   *> \verbatim
   *>          BETA is DOUBLE PRECISION
   *>           On entry, BETA specifies the scalar beta. When BETA is
   *>           supplied as zero then Y need not be set on input.
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in,out] Y
   *> \verbatim
   *>          Y is DOUBLE PRECISION array, dimension
   *>           ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'
   *>           and at least
   *>           ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.
   *>           Before entry with BETA non-zero, the incremented array Y
   *>           must contain the vector y. On exit, Y is overwritten by the
   *>           updated vector y.
   *> \endverbatim
   *>
   *> \param[in] INCY
   *> \verbatim
   *>          INCY is INTEGER
   *>           On entry, INCY specifies the increment for the elements of
   *>           Y. INCY must not be zero.
   *>           Unchanged on exit.
   *>
   *>  Level 2 Blas routine.
   *> \endverbatim
   *
   *  Authors:
   *  ========
   *
   *> \author Univ. of Tennessee 
   *> \author Univ. of California Berkeley 
   *> \author Univ. of Colorado Denver 
   *> \author NAG Ltd. 
   *
   *> \date November 2011
   *
   *> \ingroup complex16GEcomputational
   *
   *  =====================================================================
       SUBROUTINE ZLA_GEAMV ( TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA,        SUBROUTINE ZLA_GEAMV ( TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA,
      $                       Y, INCY )       $                       Y, INCY )
 *  *
 *     -- LAPACK routine (version 3.3.1)                                 --  *  -- LAPACK computational routine (version 3.4.0) --
 *     -- Contributed by James Demmel, Deaglan Halligan, Yozo Hida and --  *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
 *     -- Jason Riedy of Univ. of California Berkeley.                 --  *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
 *     -- June 2010                                                    --  *     November 2011
 *  
 *     -- LAPACK is a software package provided by Univ. of Tennessee, --  
 *     -- Univ. of California Berkeley and NAG Ltd.                    --  
 *  *
       IMPLICIT NONE  
 *     ..  
 *     .. Scalar Arguments ..  *     .. Scalar Arguments ..
       DOUBLE PRECISION   ALPHA, BETA        DOUBLE PRECISION   ALPHA, BETA
       INTEGER            INCX, INCY, LDA, M, N        INTEGER            INCX, INCY, LDA, M, N
Line 21 Line 190
       DOUBLE PRECISION   Y( * )        DOUBLE PRECISION   Y( * )
 *     ..  *     ..
 *  *
 *  Purpose  
 *  =======  
 *  
 *  ZLA_GEAMV  performs one of the matrix-vector operations  
 *  
 *          y := alpha*abs(A)*abs(x) + beta*abs(y),  
 *     or   y := alpha*abs(A)**T*abs(x) + beta*abs(y),  
 *  
 *  where alpha and beta are scalars, x and y are vectors and A is an  
 *  m by n matrix.  
 *  
 *  This function is primarily used in calculating error bounds.  
 *  To protect against underflow during evaluation, components in  
 *  the resulting vector are perturbed away from zero by (N+1)  
 *  times the underflow threshold.  To prevent unnecessarily large  
 *  errors for block-structure embedded in general matrices,  
 *  "symbolically" zero components are not perturbed.  A zero  
 *  entry is considered "symbolic" if all multiplications involved  
 *  in computing that entry have at least one zero multiplicand.  
 *  
 *  Arguments  
 *  ==========  
 *  
 *  TRANS    (input) INTEGER  
 *           On entry, TRANS specifies the operation to be performed as  
 *           follows:  
 *  
 *             BLAS_NO_TRANS      y := alpha*abs(A)*abs(x) + beta*abs(y)  
 *             BLAS_TRANS         y := alpha*abs(A**T)*abs(x) + beta*abs(y)  
 *             BLAS_CONJ_TRANS    y := alpha*abs(A**T)*abs(x) + beta*abs(y)  
 *  
 *           Unchanged on exit.  
 *  
 *  M        (input) INTEGER  
 *           On entry, M specifies the number of rows of the matrix A.  
 *           M must be at least zero.  
 *           Unchanged on exit.  
 *  
 *  N        (input) INTEGER  
 *           On entry, N specifies the number of columns of the matrix A.  
 *           N must be at least zero.  
 *           Unchanged on exit.  
 *  
 *  ALPHA    (input) DOUBLE PRECISION  
 *           On entry, ALPHA specifies the scalar alpha.  
 *           Unchanged on exit.  
 *  
 *  A        (input) COMPLEX*16 array of DIMENSION ( LDA, n )  
 *           Before entry, the leading m by n part of the array A must  
 *           contain the matrix of coefficients.  
 *           Unchanged on exit.  
 *  
 *  LDA      (input) INTEGER  
 *           On entry, LDA specifies the first dimension of A as declared  
 *           in the calling (sub) program. LDA must be at least  
 *           max( 1, m ).  
 *           Unchanged on exit.  
 *  
 *  X        (input) COMPLEX*16 array of DIMENSION at least  
 *           ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'  
 *           and at least  
 *           ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.  
 *           Before entry, the incremented array X must contain the  
 *           vector x.  
 *           Unchanged on exit.  
 *  
 *  INCX     (input) INTEGER  
 *           On entry, INCX specifies the increment for the elements of  
 *           X. INCX must not be zero.  
 *           Unchanged on exit.  
 *  
 *  BETA     (input) DOUBLE PRECISION  
 *           On entry, BETA specifies the scalar beta. When BETA is  
 *           supplied as zero then Y need not be set on input.  
 *           Unchanged on exit.  
 *  
 *  Y        (input/output) DOUBLE PRECISION  array, dimension  
 *           ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'  
 *           and at least  
 *           ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.  
 *           Before entry with BETA non-zero, the incremented array Y  
 *           must contain the vector y. On exit, Y is overwritten by the  
 *           updated vector y.  
 *  
 *  INCY     (input) INTEGER  
 *           On entry, INCY specifies the increment for the elements of  
 *           Y. INCY must not be zero.  
 *           Unchanged on exit.  
 *  
 *  
 *  Level 2 Blas routine.  
 *  
 *  =====================================================================  *  =====================================================================
 *  *
 *     .. Parameters ..  *     .. Parameters ..

Removed from v.1.5  
changed lines
  Added in v.1.6


CVSweb interface <joel.bertrand@systella.fr>