Diff for /rpl/lapack/lapack/zla_syamv.f between versions 1.4 and 1.5

version 1.4, 2010/12/21 13:53:48 version 1.5, 2011/11/21 20:43:14
Line 1 Line 1
   *> \brief \b ZLA_SYAMV
   *
   *  =========== DOCUMENTATION ===========
   *
   * Online html documentation available at 
   *            http://www.netlib.org/lapack/explore-html/ 
   *
   *> \htmlonly
   *> Download ZLA_SYAMV + dependencies 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zla_syamv.f"> 
   *> [TGZ]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zla_syamv.f"> 
   *> [ZIP]</a> 
   *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zla_syamv.f"> 
   *> [TXT]</a>
   *> \endhtmlonly 
   *
   *  Definition:
   *  ===========
   *
   *       SUBROUTINE ZLA_SYAMV( UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y,
   *                             INCY )
   * 
   *       .. Scalar Arguments ..
   *       DOUBLE PRECISION   ALPHA, BETA
   *       INTEGER            INCX, INCY, LDA, N
   *       INTEGER            UPLO
   *       ..
   *       .. Array Arguments ..
   *       COMPLEX*16         A( LDA, * ), X( * )
   *       DOUBLE PRECISION   Y( * )
   *       ..
   *  
   *
   *> \par Purpose:
   *  =============
   *>
   *> \verbatim
   *>
   *> ZLA_SYAMV  performs the matrix-vector operation
   *>
   *>         y := alpha*abs(A)*abs(x) + beta*abs(y),
   *>
   *> where alpha and beta are scalars, x and y are vectors and A is an
   *> n by n symmetric 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] UPLO
   *> \verbatim
   *>          UPLO is INTEGER
   *>           On entry, UPLO specifies whether the upper or lower
   *>           triangular part of the array A is to be referenced as
   *>           follows:
   *>
   *>              UPLO = BLAS_UPPER   Only the upper triangular part of A
   *>                                  is to be referenced.
   *>
   *>              UPLO = BLAS_LOWER   Only the lower triangular part of A
   *>                                  is to be referenced.
   *>
   *>           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, 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, n ).
   *>           Unchanged on exit.
   *> \endverbatim
   *>
   *> \param[in] X
   *> \verbatim
   *>          X is COMPLEX*16 array, DIMENSION at least
   *>           ( 1 + ( n - 1 )*abs( INCX ) )
   *>           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 + ( n - 1 )*abs( INCY ) )
   *>           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.
   *> \endverbatim
   *
   *  Authors:
   *  ========
   *
   *> \author Univ. of Tennessee 
   *> \author Univ. of California Berkeley 
   *> \author Univ. of Colorado Denver 
   *> \author NAG Ltd. 
   *
   *> \date November 2011
   *
   *> \ingroup complex16SYcomputational
   *
   *> \par Further Details:
   *  =====================
   *>
   *> \verbatim
   *>
   *>  Level 2 Blas routine.
   *>
   *>  -- Written on 22-October-1986.
   *>     Jack Dongarra, Argonne National Lab.
   *>     Jeremy Du Croz, Nag Central Office.
   *>     Sven Hammarling, Nag Central Office.
   *>     Richard Hanson, Sandia National Labs.
   *>  -- Modified for the absolute-value product, April 2006
   *>     Jason Riedy, UC Berkeley
   *> \endverbatim
   *>
   *  =====================================================================
       SUBROUTINE ZLA_SYAMV( UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y,        SUBROUTINE ZLA_SYAMV( UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y,
      $                      INCY )       $                      INCY )
 *  *
 *     -- LAPACK routine (version 3.2.2)                                 --  *  -- 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, N        INTEGER            INCX, INCY, LDA, N
Line 21 Line 194
       DOUBLE PRECISION   Y( * )        DOUBLE PRECISION   Y( * )
 *     ..  *     ..
 *  *
 *  Purpose  
 *  =======  
 *  
 *  ZLA_SYAMV  performs the matrix-vector operation  
 *  
 *          y := alpha*abs(A)*abs(x) + beta*abs(y),  
 *  
 *  where alpha and beta are scalars, x and y are vectors and A is an  
 *  n by n symmetric 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  
 *  ==========  
 *  
 *  UPLO    (input) INTEGER  
 *           On entry, UPLO specifies whether the upper or lower  
 *           triangular part of the array A is to be referenced as  
 *           follows:  
 *  
 *              UPLO = BLAS_UPPER   Only the upper triangular part of A  
 *                                  is to be referenced.  
 *  
 *              UPLO = BLAS_LOWER   Only the lower triangular part of A  
 *                                  is to be referenced.  
 *  
 *           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  - DOUBLE PRECISION   .  
 *           On entry, ALPHA specifies the scalar alpha.  
 *           Unchanged on exit.  
 *  
 *  A      - 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, n ).  
 *           Unchanged on exit.  
 *  
 *  X      - COMPLEX*16         array of DIMENSION at least  
 *           ( 1 + ( n - 1 )*abs( INCX ) )  
 *           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   - 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 + ( n - 1 )*abs( INCY ) )  
 *           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.  
 *  
 *  Further Details  
 *  ===============  
 *  
 *  Level 2 Blas routine.  
 *  
 *  -- Written on 22-October-1986.  
 *     Jack Dongarra, Argonne National Lab.  
 *     Jeremy Du Croz, Nag Central Office.  
 *     Sven Hammarling, Nag Central Office.  
 *     Richard Hanson, Sandia National Labs.  
 *  -- Modified for the absolute-value product, April 2006  
 *     Jason Riedy, UC Berkeley  
 *  
 *  =====================================================================  *  =====================================================================
 *  *
 *     .. Parameters ..  *     .. Parameters ..

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


CVSweb interface <joel.bertrand@systella.fr>