ENH: Improving the travis dashboard name
[platform/upstream/lapack.git] / SRC / cla_gbrcond_x.f
1 *> \brief \b CLA_GBRCOND_X computes the infinity norm condition number of op(A)*diag(x) for general banded matrices.
2 *
3 *  =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 *            http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CLA_GBRCOND_X + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cla_gbrcond_x.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cla_gbrcond_x.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cla_gbrcond_x.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 *  Definition:
19 *  ===========
20 *
21 *       REAL FUNCTION CLA_GBRCOND_X( TRANS, N, KL, KU, AB, LDAB, AFB,
22 *                                    LDAFB, IPIV, X, INFO, WORK, RWORK )
23 *
24 *       .. Scalar Arguments ..
25 *       CHARACTER          TRANS
26 *       INTEGER            N, KL, KU, KD, KE, LDAB, LDAFB, INFO
27 *       ..
28 *       .. Array Arguments ..
29 *       INTEGER            IPIV( * )
30 *       COMPLEX            AB( LDAB, * ), AFB( LDAFB, * ), WORK( * ),
31 *      $                   X( * )
32 *       REAL               RWORK( * )
33 *       ..
34 *
35 *
36 *> \par Purpose:
37 *  =============
38 *>
39 *> \verbatim
40 *>
41 *>    CLA_GBRCOND_X Computes the infinity norm condition number of
42 *>    op(A) * diag(X) where X is a COMPLEX vector.
43 *> \endverbatim
44 *
45 *  Arguments:
46 *  ==========
47 *
48 *> \param[in] TRANS
49 *> \verbatim
50 *>          TRANS is CHARACTER*1
51 *>     Specifies the form of the system of equations:
52 *>       = 'N':  A * X = B     (No transpose)
53 *>       = 'T':  A**T * X = B  (Transpose)
54 *>       = 'C':  A**H * X = B  (Conjugate Transpose = Transpose)
55 *> \endverbatim
56 *>
57 *> \param[in] N
58 *> \verbatim
59 *>          N is INTEGER
60 *>     The number of linear equations, i.e., the order of the
61 *>     matrix A.  N >= 0.
62 *> \endverbatim
63 *>
64 *> \param[in] KL
65 *> \verbatim
66 *>          KL is INTEGER
67 *>     The number of subdiagonals within the band of A.  KL >= 0.
68 *> \endverbatim
69 *>
70 *> \param[in] KU
71 *> \verbatim
72 *>          KU is INTEGER
73 *>     The number of superdiagonals within the band of A.  KU >= 0.
74 *> \endverbatim
75 *>
76 *> \param[in] AB
77 *> \verbatim
78 *>          AB is COMPLEX array, dimension (LDAB,N)
79 *>     On entry, the matrix A in band storage, in rows 1 to KL+KU+1.
80 *>     The j-th column of A is stored in the j-th column of the
81 *>     array AB as follows:
82 *>     AB(KU+1+i-j,j) = A(i,j) for max(1,j-KU)<=i<=min(N,j+kl)
83 *> \endverbatim
84 *>
85 *> \param[in] LDAB
86 *> \verbatim
87 *>          LDAB is INTEGER
88 *>     The leading dimension of the array AB.  LDAB >= KL+KU+1.
89 *> \endverbatim
90 *>
91 *> \param[in] AFB
92 *> \verbatim
93 *>          AFB is COMPLEX array, dimension (LDAFB,N)
94 *>     Details of the LU factorization of the band matrix A, as
95 *>     computed by CGBTRF.  U is stored as an upper triangular
96 *>     band matrix with KL+KU superdiagonals in rows 1 to KL+KU+1,
97 *>     and the multipliers used during the factorization are stored
98 *>     in rows KL+KU+2 to 2*KL+KU+1.
99 *> \endverbatim
100 *>
101 *> \param[in] LDAFB
102 *> \verbatim
103 *>          LDAFB is INTEGER
104 *>     The leading dimension of the array AFB.  LDAFB >= 2*KL+KU+1.
105 *> \endverbatim
106 *>
107 *> \param[in] IPIV
108 *> \verbatim
109 *>          IPIV is INTEGER array, dimension (N)
110 *>     The pivot indices from the factorization A = P*L*U
111 *>     as computed by CGBTRF; row i of the matrix was interchanged
112 *>     with row IPIV(i).
113 *> \endverbatim
114 *>
115 *> \param[in] X
116 *> \verbatim
117 *>          X is COMPLEX array, dimension (N)
118 *>     The vector X in the formula op(A) * diag(X).
119 *> \endverbatim
120 *>
121 *> \param[out] INFO
122 *> \verbatim
123 *>          INFO is INTEGER
124 *>       = 0:  Successful exit.
125 *>     i > 0:  The ith argument is invalid.
126 *> \endverbatim
127 *>
128 *> \param[in] WORK
129 *> \verbatim
130 *>          WORK is COMPLEX array, dimension (2*N).
131 *>     Workspace.
132 *> \endverbatim
133 *>
134 *> \param[in] RWORK
135 *> \verbatim
136 *>          RWORK is REAL array, dimension (N).
137 *>     Workspace.
138 *> \endverbatim
139 *
140 *  Authors:
141 *  ========
142 *
143 *> \author Univ. of Tennessee
144 *> \author Univ. of California Berkeley
145 *> \author Univ. of Colorado Denver
146 *> \author NAG Ltd.
147 *
148 *> \date September 2012
149 *
150 *> \ingroup complexGBcomputational
151 *
152 *  =====================================================================
153       REAL FUNCTION CLA_GBRCOND_X( TRANS, N, KL, KU, AB, LDAB, AFB,
154      $                             LDAFB, IPIV, X, INFO, WORK, RWORK )
155 *
156 *  -- LAPACK computational routine (version 3.4.2) --
157 *  -- LAPACK is a software package provided by Univ. of Tennessee,    --
158 *  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
159 *     September 2012
160 *
161 *     .. Scalar Arguments ..
162       CHARACTER          TRANS
163       INTEGER            N, KL, KU, KD, KE, LDAB, LDAFB, INFO
164 *     ..
165 *     .. Array Arguments ..
166       INTEGER            IPIV( * )
167       COMPLEX            AB( LDAB, * ), AFB( LDAFB, * ), WORK( * ),
168      $                   X( * )
169       REAL               RWORK( * )
170 *     ..
171 *
172 *  =====================================================================
173 *
174 *     .. Local Scalars ..
175       LOGICAL            NOTRANS
176       INTEGER            KASE, I, J
177       REAL               AINVNM, ANORM, TMP
178       COMPLEX            ZDUM
179 *     ..
180 *     .. Local Arrays ..
181       INTEGER            ISAVE( 3 )
182 *     ..
183 *     .. External Functions ..
184       LOGICAL            LSAME
185       EXTERNAL           LSAME
186 *     ..
187 *     .. External Subroutines ..
188       EXTERNAL           CLACN2, CGBTRS, XERBLA
189 *     ..
190 *     .. Intrinsic Functions ..
191       INTRINSIC          ABS, MAX
192 *     ..
193 *     .. Statement Functions ..
194       REAL               CABS1
195 *     ..
196 *     .. Statement Function Definitions ..
197       CABS1( ZDUM ) = ABS( REAL( ZDUM ) ) + ABS( AIMAG( ZDUM ) )
198 *     ..
199 *     .. Executable Statements ..
200 *
201       CLA_GBRCOND_X = 0.0E+0
202 *
203       INFO = 0
204       NOTRANS = LSAME( TRANS, 'N' )
205       IF ( .NOT. NOTRANS .AND. .NOT. LSAME(TRANS, 'T') .AND. .NOT.
206      $     LSAME( TRANS, 'C' ) ) THEN
207          INFO = -1
208       ELSE IF( N.LT.0 ) THEN
209          INFO = -2
210       ELSE IF( KL.LT.0 .OR. KL.GT.N-1 ) THEN
211          INFO = -3
212       ELSE IF( KU.LT.0 .OR. KU.GT.N-1 ) THEN
213          INFO = -4
214       ELSE IF( LDAB.LT.KL+KU+1 ) THEN
215          INFO = -6
216       ELSE IF( LDAFB.LT.2*KL+KU+1 ) THEN
217          INFO = -8
218       END IF
219       IF( INFO.NE.0 ) THEN
220          CALL XERBLA( 'CLA_GBRCOND_X', -INFO )
221          RETURN
222       END IF
223 *
224 *     Compute norm of op(A)*op2(C).
225 *
226       KD = KU + 1
227       KE = KL + 1
228       ANORM = 0.0
229       IF ( NOTRANS ) THEN
230          DO I = 1, N
231             TMP = 0.0E+0
232             DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
233                TMP = TMP + CABS1( AB( KD+I-J, J) * X( J ) )
234             END DO
235             RWORK( I ) = TMP
236             ANORM = MAX( ANORM, TMP )
237          END DO
238       ELSE
239          DO I = 1, N
240             TMP = 0.0E+0
241             DO J = MAX( I-KL, 1 ), MIN( I+KU, N )
242                TMP = TMP + CABS1( AB( KE-I+J, I ) * X( J ) )
243             END DO
244             RWORK( I ) = TMP
245             ANORM = MAX( ANORM, TMP )
246          END DO
247       END IF
248 *
249 *     Quick return if possible.
250 *
251       IF( N.EQ.0 ) THEN
252          CLA_GBRCOND_X = 1.0E+0
253          RETURN
254       ELSE IF( ANORM .EQ. 0.0E+0 ) THEN
255          RETURN
256       END IF
257 *
258 *     Estimate the norm of inv(op(A)).
259 *
260       AINVNM = 0.0E+0
261 *
262       KASE = 0
263    10 CONTINUE
264       CALL CLACN2( N, WORK( N+1 ), WORK, AINVNM, KASE, ISAVE )
265       IF( KASE.NE.0 ) THEN
266          IF( KASE.EQ.2 ) THEN
267 *
268 *           Multiply by R.
269 *
270             DO I = 1, N
271                WORK( I ) = WORK( I ) * RWORK( I )
272             END DO
273 *
274             IF ( NOTRANS ) THEN
275                CALL CGBTRS( 'No transpose', N, KL, KU, 1, AFB, LDAFB,
276      $              IPIV, WORK, N, INFO )
277             ELSE
278                CALL CGBTRS( 'Conjugate transpose', N, KL, KU, 1, AFB,
279      $              LDAFB, IPIV, WORK, N, INFO )
280             ENDIF
281 *
282 *           Multiply by inv(X).
283 *
284             DO I = 1, N
285                WORK( I ) = WORK( I ) / X( I )
286             END DO
287          ELSE
288 *
289 *           Multiply by inv(X**H).
290 *
291             DO I = 1, N
292                WORK( I ) = WORK( I ) / X( I )
293             END DO
294 *
295             IF ( NOTRANS ) THEN
296                CALL CGBTRS( 'Conjugate transpose', N, KL, KU, 1, AFB,
297      $              LDAFB, IPIV, WORK, N, INFO )
298             ELSE
299                CALL CGBTRS( 'No transpose', N, KL, KU, 1, AFB, LDAFB,
300      $              IPIV, WORK, N, INFO )
301             END IF
302 *
303 *           Multiply by R.
304 *
305             DO I = 1, N
306                WORK( I ) = WORK( I ) * RWORK( I )
307             END DO
308          END IF
309          GO TO 10
310       END IF
311 *
312 *     Compute the estimate of the reciprocal condition number.
313 *
314       IF( AINVNM .NE. 0.0E+0 )
315      $   CLA_GBRCOND_X = 1.0E+0 / AINVNM
316 *
317       RETURN
318 *
319       END