LAPACK 3.12.0
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 155 of file dlagtf.f.

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