Annotation of rpl/lapack/lapack/zlascl2.f, revision 1.17

1.17    ! bertrand    1: *> \brief \b ZLASCL2 performs diagonal scaling on a matrix.
1.5       bertrand    2: *
                      3: *  =========== DOCUMENTATION ===========
                      4: *
1.14      bertrand    5: * Online html documentation available at
                      6: *            http://www.netlib.org/lapack/explore-html/
1.5       bertrand    7: *
                      8: *> \htmlonly
1.14      bertrand    9: *> Download ZLASCL2 + dependencies
                     10: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlascl2.f">
                     11: *> [TGZ]</a>
                     12: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlascl2.f">
                     13: *> [ZIP]</a>
                     14: *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlascl2.f">
1.5       bertrand   15: *> [TXT]</a>
1.14      bertrand   16: *> \endhtmlonly
1.5       bertrand   17: *
                     18: *  Definition:
                     19: *  ===========
                     20: *
                     21: *       SUBROUTINE ZLASCL2 ( M, N, D, X, LDX )
1.14      bertrand   22: *
1.5       bertrand   23: *       .. Scalar Arguments ..
                     24: *       INTEGER            M, N, LDX
                     25: *       ..
                     26: *       .. Array Arguments ..
                     27: *       DOUBLE PRECISION   D( * )
                     28: *       COMPLEX*16         X( LDX, * )
                     29: *       ..
1.14      bertrand   30: *
1.5       bertrand   31: *
                     32: *> \par Purpose:
                     33: *  =============
                     34: *>
                     35: *> \verbatim
                     36: *>
1.17    ! bertrand   37: *> ZLASCL2 performs a diagonal scaling on a matrix:
1.5       bertrand   38: *>   x <-- D * x
                     39: *> where the DOUBLE PRECISION diagonal matrix D is stored as a vector.
                     40: *>
                     41: *> Eventually to be replaced by BLAS_zge_diag_scale in the new BLAS
                     42: *> standard.
                     43: *> \endverbatim
                     44: *
                     45: *  Arguments:
                     46: *  ==========
                     47: *
                     48: *> \param[in] M
                     49: *> \verbatim
                     50: *>          M is INTEGER
                     51: *>     The number of rows of D and X. M >= 0.
                     52: *> \endverbatim
                     53: *>
                     54: *> \param[in] N
                     55: *> \verbatim
                     56: *>          N is INTEGER
1.11      bertrand   57: *>     The number of columns of X. N >= 0.
1.5       bertrand   58: *> \endverbatim
                     59: *>
                     60: *> \param[in] D
                     61: *> \verbatim
                     62: *>          D is DOUBLE PRECISION array, length M
                     63: *>     Diagonal matrix D, stored as a vector of length M.
                     64: *> \endverbatim
                     65: *>
                     66: *> \param[in,out] X
                     67: *> \verbatim
                     68: *>          X is COMPLEX*16 array, dimension (LDX,N)
1.17    ! bertrand   69: *>     On entry, the matrix X to be scaled by D.
        !            70: *>     On exit, the scaled matrix.
1.5       bertrand   71: *> \endverbatim
                     72: *>
                     73: *> \param[in] LDX
                     74: *> \verbatim
                     75: *>          LDX is INTEGER
1.17    ! bertrand   76: *>     The leading dimension of the matrix X. LDX >= M.
1.5       bertrand   77: *> \endverbatim
                     78: *
                     79: *  Authors:
                     80: *  ========
                     81: *
1.14      bertrand   82: *> \author Univ. of Tennessee
                     83: *> \author Univ. of California Berkeley
                     84: *> \author Univ. of Colorado Denver
                     85: *> \author NAG Ltd.
1.5       bertrand   86: *
                     87: *> \ingroup complex16OTHERcomputational
                     88: *
                     89: *  =====================================================================
1.1       bertrand   90:       SUBROUTINE ZLASCL2 ( M, N, D, X, LDX )
                     91: *
1.17    ! bertrand   92: *  -- LAPACK computational routine --
1.5       bertrand   93: *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
                     94: *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
1.1       bertrand   95: *
                     96: *     .. Scalar Arguments ..
                     97:       INTEGER            M, N, LDX
                     98: *     ..
                     99: *     .. Array Arguments ..
                    100:       DOUBLE PRECISION   D( * )
                    101:       COMPLEX*16         X( LDX, * )
                    102: *     ..
                    103: *
                    104: *  =====================================================================
                    105: *
                    106: *     .. Local Scalars ..
                    107:       INTEGER            I, J
                    108: *     ..
                    109: *     .. Executable Statements ..
                    110: *
                    111:       DO J = 1, N
                    112:          DO I = 1, M
                    113:             X( I, J ) = X( I, J ) * D( I )
                    114:          END DO
                    115:       END DO
                    116: 
                    117:       RETURN
                    118:       END
                    119: 

CVSweb interface <joel.bertrand@systella.fr>