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

◆ dlagtf()

subroutine dlagtf ( integer n,
double precision, dimension( * ) a,
double precision lambda,
double precision, dimension( * ) b,
double precision, dimension( * ) c,
double precision tol,
double precision, dimension( * ) d,
integer, dimension( * ) in,
integer info )

DLAGTF computes an LU factorization of a matrix T-λI, where T is a general tridiagonal matrix, and λ a scalar, using partial pivoting with row interchanges.

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

Purpose:
!>
!> DLAGTF factorizes the matrix (T - lambda*I), where T is an n by n
!> tridiagonal matrix and lambda is a scalar, as
!>
!>    T - lambda*I = PLU,
!>
!> where P is a permutation matrix, L is a unit lower tridiagonal matrix
!> with at most one non-zero sub-diagonal elements per column and U is
!> an upper triangular matrix with at most two non-zero super-diagonal
!> elements per column.
!>
!> The factorization is obtained by Gaussian elimination with partial
!> pivoting and implicit row scaling.
!>
!> The parameter LAMBDA is included in the routine so that DLAGTF may
!> be used, in conjunction with DLAGTS, to obtain eigenvectors of T by
!> inverse iteration.
!> 
Parameters
[in]N
!>          N is INTEGER
!>          The order of the matrix T.
!> 
[in,out]A
!>          A is DOUBLE PRECISION array, dimension (N)
!>          On entry, A must contain the diagonal elements of T.
!>
!>          On exit, A is overwritten by the n diagonal elements of the
!>          upper triangular matrix U of the factorization of T.
!> 
[in]LAMBDA
!>          LAMBDA is DOUBLE PRECISION
!>          On entry, the scalar lambda.
!> 
[in,out]B
!>          B is DOUBLE PRECISION array, dimension (N-1)
!>          On entry, B must contain the (n-1) super-diagonal elements of
!>          T.
!>
!>          On exit, B is overwritten by the (n-1) super-diagonal
!>          elements of the matrix U of the factorization of T.
!> 
[in,out]C
!>          C is DOUBLE PRECISION array, dimension (N-1)
!>          On entry, C must contain the (n-1) sub-diagonal elements of
!>          T.
!>
!>          On exit, C is overwritten by the (n-1) sub-diagonal elements
!>          of the matrix L of the factorization of T.
!> 
[in]TOL
!>          TOL is DOUBLE PRECISION
!>          On entry, a relative tolerance used to indicate whether or
!>          not the matrix (T - lambda*I) is nearly singular. TOL should
!>          normally be chose as approximately the largest relative error
!>          in the elements of T. For example, if the elements of T are
!>          correct to about 4 significant figures, then TOL should be
!>          set to about 5*10**(-4). If TOL is supplied as less than eps,
!>          where eps is the relative machine precision, then the value
!>          eps is used in place of TOL.
!> 
[out]D
!>          D is DOUBLE PRECISION array, dimension (N-2)
!>          On exit, D is overwritten by the (n-2) second super-diagonal
!>          elements of the matrix U of the factorization of T.
!> 
[out]IN
!>          IN is INTEGER array, dimension (N)
!>          On exit, IN contains details of the permutation matrix P. If
!>          an interchange occurred at the kth step of the elimination,
!>          then IN(k) = 1, otherwise IN(k) = 0. The element IN(n)
!>          returns the smallest positive integer j such that
!>
!>             abs( u(j,j) ) <= norm( (T - lambda*I)(j) )*TOL,
!>
!>          where norm( A(j) ) denotes the sum of the absolute values of
!>          the jth row of the matrix A. If no such j exists then IN(n)
!>          is returned as zero. If IN(n) is returned as positive, then a
!>          diagonal element of U is small, indicating that
!>          (T - lambda*I) is singular or nearly singular,
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0:  successful exit
!>          < 0:  if INFO = -k, the kth argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 153 of file dlagtf.f.

154*
155* -- LAPACK computational routine --
156* -- LAPACK is a software package provided by Univ. of Tennessee, --
157* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
158*
159* .. Scalar Arguments ..
160 INTEGER INFO, N
161 DOUBLE PRECISION LAMBDA, TOL
162* ..
163* .. Array Arguments ..
164 INTEGER IN( * )
165 DOUBLE PRECISION A( * ), B( * ), C( * ), D( * )
166* ..
167*
168* =====================================================================
169*
170* .. Parameters ..
171 DOUBLE PRECISION ZERO
172 parameter( zero = 0.0d+0 )
173* ..
174* .. Local Scalars ..
175 INTEGER K
176 DOUBLE PRECISION EPS, MULT, PIV1, PIV2, SCALE1, SCALE2, TEMP, TL
177* ..
178* .. Intrinsic Functions ..
179 INTRINSIC abs, max
180* ..
181* .. External Functions ..
182 DOUBLE PRECISION DLAMCH
183 EXTERNAL dlamch
184* ..
185* .. External Subroutines ..
186 EXTERNAL xerbla
187* ..
188* .. Executable Statements ..
189*
190 info = 0
191 IF( n.LT.0 ) THEN
192 info = -1
193 CALL xerbla( 'DLAGTF', -info )
194 RETURN
195 END IF
196*
197 IF( n.EQ.0 )
198 $ RETURN
199*
200 a( 1 ) = a( 1 ) - lambda
201 in( n ) = 0
202 IF( n.EQ.1 ) THEN
203 IF( a( 1 ).EQ.zero )
204 $ in( 1 ) = 1
205 RETURN
206 END IF
207*
208 eps = dlamch( 'Epsilon' )
209*
210 tl = max( tol, eps )
211 scale1 = abs( a( 1 ) ) + abs( b( 1 ) )
212 DO 10 k = 1, n - 1
213 a( k+1 ) = a( k+1 ) - lambda
214 scale2 = abs( c( k ) ) + abs( a( k+1 ) )
215 IF( k.LT.( n-1 ) )
216 $ scale2 = scale2 + abs( b( k+1 ) )
217 IF( a( k ).EQ.zero ) THEN
218 piv1 = zero
219 ELSE
220 piv1 = abs( a( k ) ) / scale1
221 END IF
222 IF( c( k ).EQ.zero ) THEN
223 in( k ) = 0
224 piv2 = zero
225 scale1 = scale2
226 IF( k.LT.( n-1 ) )
227 $ d( k ) = zero
228 ELSE
229 piv2 = abs( c( k ) ) / scale2
230 IF( piv2.LE.piv1 ) THEN
231 in( k ) = 0
232 scale1 = scale2
233 c( k ) = c( k ) / a( k )
234 a( k+1 ) = a( k+1 ) - c( k )*b( k )
235 IF( k.LT.( n-1 ) )
236 $ d( k ) = zero
237 ELSE
238 in( k ) = 1
239 mult = a( k ) / c( k )
240 a( k ) = c( k )
241 temp = a( k+1 )
242 a( k+1 ) = b( k ) - mult*temp
243 IF( k.LT.( n-1 ) ) THEN
244 d( k ) = b( k+1 )
245 b( k+1 ) = -mult*d( k )
246 END IF
247 b( k ) = temp
248 c( k ) = mult
249 END IF
250 END IF
251 IF( ( max( piv1, piv2 ).LE.tl ) .AND. ( in( n ).EQ.0 ) )
252 $ in( n ) = k
253 10 CONTINUE
254 IF( ( abs( a( n ) ).LE.scale1*tl ) .AND. ( in( n ).EQ.0 ) )
255 $ in( n ) = n
256*
257 RETURN
258*
259* End of DLAGTF
260*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
double precision function dlamch(cmach)
DLAMCH
Definition dlamch.f:69
Here is the call graph for this function:
Here is the caller graph for this function: