LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine ctpcon ( character  NORM,
character  UPLO,
character  DIAG,
integer  N,
complex, dimension( * )  AP,
real  RCOND,
complex, dimension( * )  WORK,
real, dimension( * )  RWORK,
integer  INFO 
)

CTPCON

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

Purpose:
 CTPCON estimates the reciprocal of the condition number of a packed
 triangular matrix A, in either the 1-norm or the infinity-norm.

 The norm of A is computed and an estimate is obtained for
 norm(inv(A)), then 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]UPLO
          UPLO is CHARACTER*1
          = 'U':  A is upper triangular;
          = 'L':  A is lower triangular.
[in]DIAG
          DIAG is CHARACTER*1
          = 'N':  A is non-unit triangular;
          = 'U':  A is unit triangular.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in]AP
          AP is COMPLEX array, dimension (N*(N+1)/2)
          The upper or lower triangular matrix A, packed columnwise in
          a linear array.  The j-th column of A is stored in the array
          AP as follows:
          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = A(i,j) for j<=i<=n.
          If DIAG = 'U', the diagonal elements of A are not referenced
          and are assumed to be 1.
[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 132 of file ctpcon.f.

132 *
133 * -- LAPACK computational routine (version 3.4.0) --
134 * -- LAPACK is a software package provided by Univ. of Tennessee, --
135 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136 * November 2011
137 *
138 * .. Scalar Arguments ..
139  CHARACTER diag, norm, uplo
140  INTEGER info, n
141  REAL rcond
142 * ..
143 * .. Array Arguments ..
144  REAL rwork( * )
145  COMPLEX ap( * ), work( * )
146 * ..
147 *
148 * =====================================================================
149 *
150 * .. Parameters ..
151  REAL one, zero
152  parameter ( one = 1.0e+0, zero = 0.0e+0 )
153 * ..
154 * .. Local Scalars ..
155  LOGICAL nounit, onenrm, upper
156  CHARACTER normin
157  INTEGER ix, kase, kase1
158  REAL ainvnm, anorm, scale, smlnum, xnorm
159  COMPLEX zdum
160 * ..
161 * .. Local Arrays ..
162  INTEGER isave( 3 )
163 * ..
164 * .. External Functions ..
165  LOGICAL lsame
166  INTEGER icamax
167  REAL clantp, slamch
168  EXTERNAL lsame, icamax, clantp, slamch
169 * ..
170 * .. External Subroutines ..
171  EXTERNAL clacn2, clatps, csrscl, xerbla
172 * ..
173 * .. Intrinsic Functions ..
174  INTRINSIC abs, aimag, max, real
175 * ..
176 * .. Statement Functions ..
177  REAL cabs1
178 * ..
179 * .. Statement Function definitions ..
180  cabs1( zdum ) = abs( REAL( ZDUM ) ) + abs( aimag( zdum ) )
181 * ..
182 * .. Executable Statements ..
183 *
184 * Test the input parameters.
185 *
186  info = 0
187  upper = lsame( uplo, 'U' )
188  onenrm = norm.EQ.'1' .OR. lsame( norm, 'O' )
189  nounit = lsame( diag, 'N' )
190 *
191  IF( .NOT.onenrm .AND. .NOT.lsame( norm, 'I' ) ) THEN
192  info = -1
193  ELSE IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
194  info = -2
195  ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
196  info = -3
197  ELSE IF( n.LT.0 ) THEN
198  info = -4
199  END IF
200  IF( info.NE.0 ) THEN
201  CALL xerbla( 'CTPCON', -info )
202  RETURN
203  END IF
204 *
205 * Quick return if possible
206 *
207  IF( n.EQ.0 ) THEN
208  rcond = one
209  RETURN
210  END IF
211 *
212  rcond = zero
213  smlnum = slamch( 'Safe minimum' )*REAL( MAX( 1, N ) )
214 *
215 * Compute the norm of the triangular matrix A.
216 *
217  anorm = clantp( norm, uplo, diag, n, ap, rwork )
218 *
219 * Continue only if ANORM > 0.
220 *
221  IF( anorm.GT.zero ) THEN
222 *
223 * Estimate the norm of the inverse of A.
224 *
225  ainvnm = zero
226  normin = 'N'
227  IF( onenrm ) THEN
228  kase1 = 1
229  ELSE
230  kase1 = 2
231  END IF
232  kase = 0
233  10 CONTINUE
234  CALL clacn2( n, work( n+1 ), work, ainvnm, kase, isave )
235  IF( kase.NE.0 ) THEN
236  IF( kase.EQ.kase1 ) THEN
237 *
238 * Multiply by inv(A).
239 *
240  CALL clatps( uplo, 'No transpose', diag, normin, n, ap,
241  $ work, scale, rwork, info )
242  ELSE
243 *
244 * Multiply by inv(A**H).
245 *
246  CALL clatps( uplo, 'Conjugate transpose', diag, normin,
247  $ n, ap, work, scale, rwork, info )
248  END IF
249  normin = 'Y'
250 *
251 * Multiply by 1/SCALE if doing so will not cause overflow.
252 *
253  IF( scale.NE.one ) THEN
254  ix = icamax( n, work, 1 )
255  xnorm = cabs1( work( ix ) )
256  IF( scale.LT.xnorm*smlnum .OR. scale.EQ.zero )
257  $ GO TO 20
258  CALL csrscl( n, scale, work, 1 )
259  END IF
260  GO TO 10
261  END IF
262 *
263 * Compute the estimate of the reciprocal condition number.
264 *
265  IF( ainvnm.NE.zero )
266  $ rcond = ( one / anorm ) / ainvnm
267  END IF
268 *
269  20 CONTINUE
270  RETURN
271 *
272 * End of CTPCON
273 *
subroutine clatps(UPLO, TRANS, DIAG, NORMIN, N, AP, X, SCALE, CNORM, INFO)
CLATPS solves a triangular system of equations with the matrix held in packed storage.
Definition: clatps.f:233
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
real function clantp(NORM, UPLO, DIAG, N, AP, WORK)
CLANTP returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a triangular matrix supplied in packed form.
Definition: clantp.f:127
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
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: