ENH: Improving the travis dashboard name
[platform/upstream/lapack.git] / SRC / claqge.f
1 *> \brief \b CLAQGE scales a general rectangular matrix, using row and column scaling factors computed by sgeequ.
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CLAQGE + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/claqge.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/claqge.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/claqge.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       SUBROUTINE CLAQGE( M, N, A, LDA, R, C, ROWCND, COLCND, AMAX,
22 *                          EQUED )
23 *
24 *       .. Scalar Arguments ..
25 *       CHARACTER          EQUED
26 *       INTEGER            LDA, M, N
27 *       REAL               AMAX, COLCND, ROWCND
28 *       ..
29 *       .. Array Arguments ..
30 *       REAL               C( * ), R( * )
31 *       COMPLEX            A( LDA, * )
32 *       ..
33 *
34 *
35 *> \par Purpose:
36 *  =============
37 *>
38 *> \verbatim
39 *>
40 *> CLAQGE equilibrates a general M by N matrix A using the row and
41 *> column scaling factors in the vectors R and C.
42 *> \endverbatim
43 *
44 *  Arguments:
45 *  ==========
46 *
47 *> \param[in] M
48 *> \verbatim
49 *>          M is INTEGER
50 *>          The number of rows of the matrix A.  M >= 0.
51 *> \endverbatim
52 *>
53 *> \param[in] N
54 *> \verbatim
55 *>          N is INTEGER
56 *>          The number of columns of the matrix A.  N >= 0.
57 *> \endverbatim
58 *>
59 *> \param[in,out] A
60 *> \verbatim
61 *>          A is COMPLEX array, dimension (LDA,N)
62 *>          On entry, the M by N matrix A.
63 *>          On exit, the equilibrated matrix.  See EQUED for the form of
64 *>          the equilibrated matrix.
65 *> \endverbatim
66 *>
67 *> \param[in] LDA
68 *> \verbatim
69 *>          LDA is INTEGER
70 *>          The leading dimension of the array A.  LDA >= max(M,1).
71 *> \endverbatim
72 *>
73 *> \param[in] R
74 *> \verbatim
75 *>          R is REAL array, dimension (M)
76 *>          The row scale factors for A.
77 *> \endverbatim
78 *>
79 *> \param[in] C
80 *> \verbatim
81 *>          C is REAL array, dimension (N)
82 *>          The column scale factors for A.
83 *> \endverbatim
84 *>
85 *> \param[in] ROWCND
86 *> \verbatim
87 *>          ROWCND is REAL
88 *>          Ratio of the smallest R(i) to the largest R(i).
89 *> \endverbatim
90 *>
91 *> \param[in] COLCND
92 *> \verbatim
93 *>          COLCND is REAL
94 *>          Ratio of the smallest C(i) to the largest C(i).
95 *> \endverbatim
96 *>
97 *> \param[in] AMAX
98 *> \verbatim
99 *>          AMAX is REAL
100 *>          Absolute value of largest matrix entry.
101 *> \endverbatim
102 *>
103 *> \param[out] EQUED
104 *> \verbatim
105 *>          EQUED is CHARACTER*1
106 *>          Specifies the form of equilibration that was done.
107 *>          = 'N':  No equilibration
108 *>          = 'R':  Row equilibration, i.e., A has been premultiplied by
109 *>                  diag(R).
110 *>          = 'C':  Column equilibration, i.e., A has been postmultiplied
111 *>                  by diag(C).
112 *>          = 'B':  Both row and column equilibration, i.e., A has been
113 *>                  replaced by diag(R) * A * diag(C).
114 *> \endverbatim
115 *
116 *> \par Internal Parameters:
117 *  =========================
118 *>
119 *> \verbatim
120 *>  THRESH is a threshold value used to decide if row or column scaling
121 *>  should be done based on the ratio of the row or column scaling
122 *>  factors.  If ROWCND < THRESH, row scaling is done, and if
123 *>  COLCND < THRESH, column scaling is done.
124 *>
125 *>  LARGE and SMALL are threshold values used to decide if row scaling
126 *>  should be done based on the absolute size of the largest matrix
127 *>  element.  If AMAX > LARGE or AMAX < SMALL, row scaling is done.
128 *> \endverbatim
129 *
130 *  Authors:
131 *  ========
132 *
133 *> \author Univ. of Tennessee
134 *> \author Univ. of California Berkeley
135 *> \author Univ. of Colorado Denver
136 *> \author NAG Ltd.
137 *
138 *> \date September 2012
139 *
140 *> \ingroup complexGEauxiliary
141 *
142 *  =====================================================================
143       SUBROUTINE CLAQGE( M, N, A, LDA, R, C, ROWCND, COLCND, AMAX,
144      $                   EQUED )
145 *
146 *  -- LAPACK auxiliary routine (version 3.4.2) --
147 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
148 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
149 *     September 2012
150 *
151 *     .. Scalar Arguments ..
152       CHARACTER          EQUED
153       INTEGER            LDA, M, N
154       REAL               AMAX, COLCND, ROWCND
155 *     ..
156 *     .. Array Arguments ..
157       REAL               C( * ), R( * )
158       COMPLEX            A( LDA, * )
159 *     ..
160 *
161 *  =====================================================================
162 *
163 *     .. Parameters ..
164       REAL               ONE, THRESH
165       PARAMETER          ( ONE = 1.0E+0, THRESH = 0.1E+0 )
166 *     ..
167 *     .. Local Scalars ..
168       INTEGER            I, J
169       REAL               CJ, LARGE, SMALL
170 *     ..
171 *     .. External Functions ..
172       REAL               SLAMCH
173       EXTERNAL           SLAMCH
174 *     ..
175 *     .. Executable Statements ..
176 *
177 *     Quick return if possible
178 *
179       IF( M.LE.0 .OR. N.LE.0 ) THEN
180          EQUED = 'N'
181          RETURN
182       END IF
183 *
184 *     Initialize LARGE and SMALL.
185 *
186       SMALL = SLAMCH( 'Safe minimum' ) / SLAMCH( 'Precision' )
187       LARGE = ONE / SMALL
188 *
189       IF( ROWCND.GE.THRESH .AND. AMAX.GE.SMALL .AND. AMAX.LE.LARGE )
190      $     THEN
191 *
192 *        No row scaling
193 *
194          IF( COLCND.GE.THRESH ) THEN
195 *
196 *           No column scaling
197 *
198             EQUED = 'N'
199          ELSE
200 *
201 *           Column scaling
202 *
203             DO 20 J = 1, N
204                CJ = C( J )
205                DO 10 I = 1, M
206                   A( I, J ) = CJ*A( I, J )
207    10          CONTINUE
208    20       CONTINUE
209             EQUED = 'C'
210          END IF
211       ELSE IF( COLCND.GE.THRESH ) THEN
212 *
213 *        Row scaling, no column scaling
214 *
215          DO 40 J = 1, N
216             DO 30 I = 1, M
217                A( I, J ) = R( I )*A( I, J )
218    30       CONTINUE
219    40    CONTINUE
220          EQUED = 'R'
221       ELSE
222 *
223 *        Row and column scaling
224 *
225          DO 60 J = 1, N
226             CJ = C( J )
227             DO 50 I = 1, M
228                A( I, J ) = CJ*R( I )*A( I, J )
229    50       CONTINUE
230    60    CONTINUE
231          EQUED = 'B'
232       END IF
233 *
234       RETURN
235 *
236 *     End of CLAQGE
237 *
238       END