LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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) ).le. 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
          .lt. 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.
Date
September 2012

Definition at line 158 of file dlagtf.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: