LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cgbcon ( character  NORM,
integer  N,
integer  KL,
integer  KU,
complex, dimension( ldab, * )  AB,
integer  LDAB,
integer, dimension( * )  IPIV,
real  ANORM,
real  RCOND,
complex, dimension( * )  WORK,
real, dimension( * )  RWORK,
integer  INFO 
)

CGBCON

Download CGBCON + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 CGBCON estimates the reciprocal of the condition number of a complex
 general band matrix A, in either the 1-norm or the infinity-norm,
 using the LU factorization computed by CGBTRF.

 An estimate is obtained for norm(inv(A)), and the reciprocal of the
 condition number is computed as
    RCOND = 1 / ( norm(A) * norm(inv(A)) ).
Parameters
[in]NORM
          NORM is CHARACTER*1
          Specifies whether the 1-norm condition number or the
          infinity-norm condition number is required:
          = '1' or 'O':  1-norm;
          = 'I':         Infinity-norm.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]KL
          KL is INTEGER
          The number of subdiagonals within the band of A.  KL >= 0.
[in]KU
          KU is INTEGER
          The number of superdiagonals within the band of A.  KU >= 0.
[in]AB
          AB is COMPLEX array, dimension (LDAB,N)
          Details of the LU factorization of the band matrix A, as
          computed by CGBTRF.  U is stored as an upper triangular band
          matrix with KL+KU superdiagonals in rows 1 to KL+KU+1, and
          the multipliers used during the factorization are stored in
          rows KL+KU+2 to 2*KL+KU+1.
[in]LDAB
          LDAB is INTEGER
          The leading dimension of the array AB.  LDAB >= 2*KL+KU+1.
[in]IPIV
          IPIV is INTEGER array, dimension (N)
          The pivot indices; for 1 <= i <= N, row i of the matrix was
          interchanged with row IPIV(i).
[in]ANORM
          ANORM is REAL
          If NORM = '1' or 'O', the 1-norm of the original matrix A.
          If NORM = 'I', the infinity-norm of the original matrix A.
[out]RCOND
          RCOND is REAL
          The reciprocal of the condition number of the matrix A,
          computed as RCOND = 1/(norm(A) * norm(inv(A))).
[out]WORK
          WORK is COMPLEX array, dimension (2*N)
[out]RWORK
          RWORK is REAL array, dimension (N)
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0: if INFO = -i, the i-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 149 of file cgbcon.f.

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 *
subroutine clatbs(UPLO, TRANS, DIAG, NORMIN, N, KD, AB, LDAB, X, SCALE, CNORM, INFO)
CLATBS solves a triangular banded system of equations.
Definition: clatbs.f:245
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
complex function cdotc(N, CX, INCX, CY, INCY)
CDOTC
Definition: cdotc.f:54
integer function icamax(N, CX, INCX)
ICAMAX
Definition: icamax.f:53
subroutine csrscl(N, SA, SX, INCX)
CSRSCL multiplies a vector by the reciprocal of a real scalar.
Definition: csrscl.f:86
real function slamch(CMACH)
SLAMCH
Definition: slamch.f:69
subroutine caxpy(N, CA, CX, INCX, CY, INCY)
CAXPY
Definition: caxpy.f:53
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine clacn2(N, V, X, EST, KASE, ISAVE)
CLACN2 estimates the 1-norm of a square matrix, using reverse communication for evaluating matrix-vec...
Definition: clacn2.f:135

Here is the call graph for this function:

Here is the caller graph for this function: