LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ sptcon()

subroutine sptcon ( integer n,
real, dimension( * ) d,
real, dimension( * ) e,
real anorm,
real rcond,
real, dimension( * ) work,
integer info )

SPTCON

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

Purpose:
!>
!> SPTCON computes the reciprocal of the condition number (in the
!> 1-norm) of a real symmetric positive definite tridiagonal matrix
!> using the factorization A = L*D*L**T or A = U**T*D*U computed by
!> SPTTRF.
!>
!> Norm(inv(A)) is computed by a direct method, and the reciprocal of
!> the condition number is computed as
!>              RCOND = 1 / (ANORM * norm(inv(A))).
!> 
Parameters
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in]D
!>          D is REAL array, dimension (N)
!>          The n diagonal elements of the diagonal matrix D from the
!>          factorization of A, as computed by SPTTRF.
!> 
[in]E
!>          E is REAL array, dimension (N-1)
!>          The (n-1) off-diagonal elements of the unit bidiagonal factor
!>          U or L from the factorization of A,  as computed by SPTTRF.
!> 
[in]ANORM
!>          ANORM is REAL
!>          The 1-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/(ANORM * AINVNM), where AINVNM is the
!>          1-norm of inv(A) computed in this routine.
!> 
[out]WORK
!>          WORK 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.
Further Details:
!>
!>  The method used is described in Nicholas J. Higham, , SIAM J. Sci. Stat. Comput., Vol. 7, No. 1, January 1986.
!> 

Definition at line 115 of file sptcon.f.

116*
117* -- LAPACK computational routine --
118* -- LAPACK is a software package provided by Univ. of Tennessee, --
119* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
120*
121* .. Scalar Arguments ..
122 INTEGER INFO, N
123 REAL ANORM, RCOND
124* ..
125* .. Array Arguments ..
126 REAL D( * ), E( * ), WORK( * )
127* ..
128*
129* =====================================================================
130*
131* .. Parameters ..
132 REAL ONE, ZERO
133 parameter( one = 1.0e+0, zero = 0.0e+0 )
134* ..
135* .. Local Scalars ..
136 INTEGER I, IX
137 REAL AINVNM
138* ..
139* .. External Functions ..
140 INTEGER ISAMAX
141 EXTERNAL isamax
142* ..
143* .. External Subroutines ..
144 EXTERNAL xerbla
145* ..
146* .. Intrinsic Functions ..
147 INTRINSIC abs
148* ..
149* .. Executable Statements ..
150*
151* Test the input arguments.
152*
153 info = 0
154 IF( n.LT.0 ) THEN
155 info = -1
156 ELSE IF( anorm.LT.zero ) THEN
157 info = -4
158 END IF
159 IF( info.NE.0 ) THEN
160 CALL xerbla( 'SPTCON', -info )
161 RETURN
162 END IF
163*
164* Quick return if possible
165*
166 rcond = zero
167 IF( n.EQ.0 ) THEN
168 rcond = one
169 RETURN
170 ELSE IF( anorm.EQ.zero ) THEN
171 RETURN
172 END IF
173*
174* Check that D(1:N) is positive.
175*
176 DO 10 i = 1, n
177 IF( d( i ).LE.zero )
178 $ RETURN
179 10 CONTINUE
180*
181* Solve M(A) * x = e, where M(A) = (m(i,j)) is given by
182*
183* m(i,j) = abs(A(i,j)), i = j,
184* m(i,j) = -abs(A(i,j)), i .ne. j,
185*
186* and e = [ 1, 1, ..., 1 ]**T. Note M(A) = M(L)*D*M(L)**T.
187*
188* Solve M(L) * x = e.
189*
190 work( 1 ) = one
191 DO 20 i = 2, n
192 work( i ) = one + work( i-1 )*abs( e( i-1 ) )
193 20 CONTINUE
194*
195* Solve D * M(L)**T * x = b.
196*
197 work( n ) = work( n ) / d( n )
198 DO 30 i = n - 1, 1, -1
199 work( i ) = work( i ) / d( i ) + work( i+1 )*abs( e( i ) )
200 30 CONTINUE
201*
202* Compute AINVNM = max(x(i)), 1<=i<=n.
203*
204 ix = isamax( n, work, 1 )
205 ainvnm = abs( work( ix ) )
206*
207* Compute the reciprocal condition number.
208*
209 IF( ainvnm.NE.zero )
210 $ rcond = ( one / ainvnm ) / anorm
211*
212 RETURN
213*
214* End of SPTCON
215*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function isamax(n, sx, incx)
ISAMAX
Definition isamax.f:71
Here is the call graph for this function:
Here is the caller graph for this function: