LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cgbcon.f
Go to the documentation of this file.
1 *> \brief \b CGBCON
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CGBCON + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgbcon.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgbcon.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgbcon.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CGBCON( NORM, N, KL, KU, AB, LDAB, IPIV, ANORM, RCOND,
22 * WORK, RWORK, INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER NORM
26 * INTEGER INFO, KL, KU, LDAB, N
27 * REAL ANORM, RCOND
28 * ..
29 * .. Array Arguments ..
30 * INTEGER IPIV( * )
31 * REAL RWORK( * )
32 * COMPLEX AB( LDAB, * ), WORK( * )
33 * ..
34 *
35 *
36 *> \par Purpose:
37 * =============
38 *>
39 *> \verbatim
40 *>
41 *> CGBCON estimates the reciprocal of the condition number of a complex
42 *> general band matrix A, in either the 1-norm or the infinity-norm,
43 *> using the LU factorization computed by CGBTRF.
44 *>
45 *> An estimate is obtained for norm(inv(A)), and the reciprocal of the
46 *> condition number is computed as
47 *> RCOND = 1 / ( norm(A) * norm(inv(A)) ).
48 *> \endverbatim
49 *
50 * Arguments:
51 * ==========
52 *
53 *> \param[in] NORM
54 *> \verbatim
55 *> NORM is CHARACTER*1
56 *> Specifies whether the 1-norm condition number or the
57 *> infinity-norm condition number is required:
58 *> = '1' or 'O': 1-norm;
59 *> = 'I': Infinity-norm.
60 *> \endverbatim
61 *>
62 *> \param[in] N
63 *> \verbatim
64 *> N is INTEGER
65 *> The order of the matrix A. N >= 0.
66 *> \endverbatim
67 *>
68 *> \param[in] KL
69 *> \verbatim
70 *> KL is INTEGER
71 *> The number of subdiagonals within the band of A. KL >= 0.
72 *> \endverbatim
73 *>
74 *> \param[in] KU
75 *> \verbatim
76 *> KU is INTEGER
77 *> The number of superdiagonals within the band of A. KU >= 0.
78 *> \endverbatim
79 *>
80 *> \param[in] AB
81 *> \verbatim
82 *> AB is COMPLEX array, dimension (LDAB,N)
83 *> Details of the LU factorization of the band matrix A, as
84 *> computed by CGBTRF. U is stored as an upper triangular band
85 *> matrix with KL+KU superdiagonals in rows 1 to KL+KU+1, and
86 *> the multipliers used during the factorization are stored in
87 *> rows KL+KU+2 to 2*KL+KU+1.
88 *> \endverbatim
89 *>
90 *> \param[in] LDAB
91 *> \verbatim
92 *> LDAB is INTEGER
93 *> The leading dimension of the array AB. LDAB >= 2*KL+KU+1.
94 *> \endverbatim
95 *>
96 *> \param[in] IPIV
97 *> \verbatim
98 *> IPIV is INTEGER array, dimension (N)
99 *> The pivot indices; for 1 <= i <= N, row i of the matrix was
100 *> interchanged with row IPIV(i).
101 *> \endverbatim
102 *>
103 *> \param[in] ANORM
104 *> \verbatim
105 *> ANORM is REAL
106 *> If NORM = '1' or 'O', the 1-norm of the original matrix A.
107 *> If NORM = 'I', the infinity-norm of the original matrix A.
108 *> \endverbatim
109 *>
110 *> \param[out] RCOND
111 *> \verbatim
112 *> RCOND is REAL
113 *> The reciprocal of the condition number of the matrix A,
114 *> computed as RCOND = 1/(norm(A) * norm(inv(A))).
115 *> \endverbatim
116 *>
117 *> \param[out] WORK
118 *> \verbatim
119 *> WORK is COMPLEX array, dimension (2*N)
120 *> \endverbatim
121 *>
122 *> \param[out] RWORK
123 *> \verbatim
124 *> RWORK is REAL array, dimension (N)
125 *> \endverbatim
126 *>
127 *> \param[out] INFO
128 *> \verbatim
129 *> INFO is INTEGER
130 *> = 0: successful exit
131 *> < 0: if INFO = -i, the i-th argument had an illegal value
132 *> \endverbatim
133 *
134 * Authors:
135 * ========
136 *
137 *> \author Univ. of Tennessee
138 *> \author Univ. of California Berkeley
139 *> \author Univ. of Colorado Denver
140 *> \author NAG Ltd.
141 *
142 *> \date November 2011
143 *
144 *> \ingroup complexGBcomputational
145 *
146 * =====================================================================
147  SUBROUTINE cgbcon( NORM, N, KL, KU, AB, LDAB, IPIV, ANORM, RCOND,
148  $ work, rwork, info )
149 *
150 * -- LAPACK computational routine (version 3.4.0) --
151 * -- LAPACK is a software package provided by Univ. of Tennessee, --
152 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
153 * November 2011
154 *
155 * .. Scalar Arguments ..
156  CHARACTER norm
157  INTEGER info, kl, ku, ldab, n
158  REAL anorm, rcond
159 * ..
160 * .. Array Arguments ..
161  INTEGER ipiv( * )
162  REAL rwork( * )
163  COMPLEX ab( ldab, * ), work( * )
164 * ..
165 *
166 * =====================================================================
167 *
168 * .. Parameters ..
169  REAL one, zero
170  parameter( one = 1.0e+0, zero = 0.0e+0 )
171 * ..
172 * .. Local Scalars ..
173  LOGICAL lnoti, onenrm
174  CHARACTER normin
175  INTEGER ix, j, jp, kase, kase1, kd, lm
176  REAL ainvnm, scale, smlnum
177  COMPLEX t, zdum
178 * ..
179 * .. Local Arrays ..
180  INTEGER isave( 3 )
181 * ..
182 * .. External Functions ..
183  LOGICAL lsame
184  INTEGER icamax
185  REAL slamch
186  COMPLEX cdotc
187  EXTERNAL lsame, icamax, slamch, cdotc
188 * ..
189 * .. External Subroutines ..
190  EXTERNAL caxpy, clacn2, clatbs, csrscl, xerbla
191 * ..
192 * .. Intrinsic Functions ..
193  INTRINSIC abs, aimag, min, real
194 * ..
195 * .. Statement Functions ..
196  REAL cabs1
197 * ..
198 * .. Statement Function definitions ..
199  cabs1( zdum ) = abs( REAL( ZDUM ) ) + abs( aimag( zdum ) )
200 * ..
201 * .. Executable Statements ..
202 *
203 * Test the input parameters.
204 *
205  info = 0
206  onenrm = norm.EQ.'1' .OR. lsame( norm, 'O' )
207  IF( .NOT.onenrm .AND. .NOT.lsame( norm, 'I' ) ) THEN
208  info = -1
209  ELSE IF( n.LT.0 ) THEN
210  info = -2
211  ELSE IF( kl.LT.0 ) THEN
212  info = -3
213  ELSE IF( ku.LT.0 ) THEN
214  info = -4
215  ELSE IF( ldab.LT.2*kl+ku+1 ) THEN
216  info = -6
217  ELSE IF( anorm.LT.zero ) THEN
218  info = -8
219  END IF
220  IF( info.NE.0 ) THEN
221  CALL xerbla( 'CGBCON', -info )
222  return
223  END IF
224 *
225 * Quick return if possible
226 *
227  rcond = zero
228  IF( n.EQ.0 ) THEN
229  rcond = one
230  return
231  ELSE IF( anorm.EQ.zero ) THEN
232  return
233  END IF
234 *
235  smlnum = slamch( 'Safe minimum' )
236 *
237 * Estimate the norm of inv(A).
238 *
239  ainvnm = zero
240  normin = 'N'
241  IF( onenrm ) THEN
242  kase1 = 1
243  ELSE
244  kase1 = 2
245  END IF
246  kd = kl + ku + 1
247  lnoti = kl.GT.0
248  kase = 0
249  10 continue
250  CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
251  IF( kase.NE.0 ) THEN
252  IF( kase.EQ.kase1 ) THEN
253 *
254 * Multiply by inv(L).
255 *
256  IF( lnoti ) THEN
257  DO 20 j = 1, n - 1
258  lm = min( kl, n-j )
259  jp = ipiv( j )
260  t = work( jp )
261  IF( jp.NE.j ) THEN
262  work( jp ) = work( j )
263  work( j ) = t
264  END IF
265  CALL caxpy( lm, -t, ab( kd+1, j ), 1, work( j+1 ), 1 )
266  20 continue
267  END IF
268 *
269 * Multiply by inv(U).
270 *
271  CALL clatbs( 'Upper', 'No transpose', 'Non-unit', normin, n,
272  $ kl+ku, ab, ldab, work, scale, rwork, info )
273  ELSE
274 *
275 * Multiply by inv(U**H).
276 *
277  CALL clatbs( 'Upper', 'Conjugate transpose', 'Non-unit',
278  $ normin, n, kl+ku, ab, ldab, work, scale, rwork,
279  $ info )
280 *
281 * Multiply by inv(L**H).
282 *
283  IF( lnoti ) THEN
284  DO 30 j = n - 1, 1, -1
285  lm = min( kl, n-j )
286  work( j ) = work( j ) - cdotc( lm, ab( kd+1, j ), 1,
287  $ work( j+1 ), 1 )
288  jp = ipiv( j )
289  IF( jp.NE.j ) THEN
290  t = work( jp )
291  work( jp ) = work( j )
292  work( j ) = t
293  END IF
294  30 continue
295  END IF
296  END IF
297 *
298 * Divide X by 1/SCALE if doing so will not cause overflow.
299 *
300  normin = 'Y'
301  IF( scale.NE.one ) THEN
302  ix = icamax( n, work, 1 )
303  IF( scale.LT.cabs1( work( ix ) )*smlnum .OR. scale.EQ.zero )
304  $ go to 40
305  CALL csrscl( n, scale, work, 1 )
306  END IF
307  go to 10
308  END IF
309 *
310 * Compute the estimate of the reciprocal condition number.
311 *
312  IF( ainvnm.NE.zero )
313  $ rcond = ( one / ainvnm ) / anorm
314 *
315  40 continue
316  return
317 *
318 * End of CGBCON
319 *
320  END