1*> \brief \b CLARSCL2 performs reciprocal diagonal scaling on a vector.
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download CLARSCL2 + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clarscl2.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clarscl2.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clarscl2.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE CLARSCL2 ( M, N, D, X, LDX )
22*
23*       .. Scalar Arguments ..
24*       INTEGER            M, N, LDX
25*       ..
26*       .. Array Arguments ..
27*       COMPLEX            X( LDX, * )
28*       REAL               D( * )
29*       ..
30*
31*
32*> \par Purpose:
33*  =============
34*>
35*> \verbatim
36*>
37*> CLARSCL2 performs a reciprocal diagonal scaling on an vector:
38*>   x <-- inv(D) * x
39*> where the REAL diagonal matrix D is stored as a vector.
40*>
41*> Eventually to be replaced by BLAS_cge_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
57*>     The number of columns of X. N >= 0.
58*> \endverbatim
59*>
60*> \param[in] D
61*> \verbatim
62*>          D is REAL 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 array, dimension (LDX,N)
69*>     On entry, the vector X to be scaled by D.
70*>     On exit, the scaled vector.
71*> \endverbatim
72*>
73*> \param[in] LDX
74*> \verbatim
75*>          LDX is INTEGER
76*>     The leading dimension of the vector X. LDX >= M.
77*> \endverbatim
78*
79*  Authors:
80*  ========
81*
82*> \author Univ. of Tennessee
83*> \author Univ. of California Berkeley
84*> \author Univ. of Colorado Denver
85*> \author NAG Ltd.
86*
87*> \ingroup complexOTHERcomputational
88*
89*  =====================================================================
90      SUBROUTINE CLARSCL2 ( M, N, D, X, LDX )
91*
92*  -- LAPACK computational routine --
93*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
94*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
95*
96*     .. Scalar Arguments ..
97      INTEGER            M, N, LDX
98*     ..
99*     .. Array Arguments ..
100      COMPLEX            X( LDX, * )
101      REAL               D( * )
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
120