Annotation of rpl/lapack/lapack/dlascl2.f, revision 1.10

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

CVSweb interface <joel.bertrand@systella.fr>