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

1.1       bertrand    1:       SUBROUTINE DLASCL2 ( M, N, D, X, LDX )
                      2: *
                      3: *     -- LAPACK routine (version 3.2.1)                               --
                      4: *     -- Contributed by James Demmel, Deaglan Halligan, Yozo Hida and --
                      5: *     -- Jason Riedy of Univ. of California Berkeley.                 --
                      6: *     -- April 2009                                                   --
                      7: *
                      8: *     -- LAPACK is a software package provided by Univ. of Tennessee, --
                      9: *     -- Univ. of California Berkeley and NAG Ltd.                    --
                     10: *
                     11:       IMPLICIT NONE
                     12: *     ..
                     13: *     .. Scalar Arguments ..
                     14:       INTEGER            M, N, LDX
                     15: *     ..
                     16: *     .. Array Arguments ..
                     17:       DOUBLE PRECISION   D( * ), X( LDX, * )
                     18: *     ..
                     19: *
                     20: *  Purpose
                     21: *  =======
                     22: *
                     23: *  DLASCL2 performs a diagonal scaling on a vector:
                     24: *    x <-- D * x
                     25: *  where the diagonal matrix D is stored as a vector.
                     26: *
                     27: *  Eventually to be replaced by BLAS_dge_diag_scale in the new BLAS
                     28: *  standard.
                     29: *
                     30: *  Arguments
                     31: *  =========
                     32: *
                     33: *     M       (input) INTEGER
                     34: *     The number of rows of D and X. M >= 0.
                     35: *
                     36: *     N       (input) INTEGER
                     37: *     The number of columns of D and X. N >= 0.
                     38: *
                     39: *     D       (input) DOUBLE PRECISION array, length M
                     40: *     Diagonal matrix D, stored as a vector of length M.
                     41: *
                     42: *     X       (input/output) DOUBLE PRECISION array, dimension (LDX,N)
                     43: *     On entry, the vector X to be scaled by D.
                     44: *     On exit, the scaled vector.
                     45: *
                     46: *     LDX     (input) INTEGER
                     47: *     The leading dimension of the vector X. LDX >= 0.
                     48: *
                     49: *  =====================================================================
                     50: *
                     51: *     .. Local Scalars ..
                     52:       INTEGER            I, J
                     53: *     ..
                     54: *     .. Executable Statements ..
                     55: *
                     56:       DO J = 1, N
                     57:          DO I = 1, M
                     58:             X( I, J ) = X( I, J ) * D( I )
                     59:          END DO
                     60:       END DO
                     61: 
                     62:       RETURN
                     63:       END

CVSweb interface <joel.bertrand@systella.fr>