LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dgttrf ( integer  N,
double precision, dimension( * )  DL,
double precision, dimension( * )  D,
double precision, dimension( * )  DU,
double precision, dimension( * )  DU2,
integer, dimension( * )  IPIV,
integer  INFO 
)

DGTTRF

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

Purpose:
 DGTTRF computes an LU factorization of a real tridiagonal matrix A
 using elimination with partial pivoting and row interchanges.

 The factorization has the form
    A = L * U
 where L is a product of permutation and unit lower bidiagonal
 matrices and U is upper triangular with nonzeros in only the main
 diagonal and first two superdiagonals.
Parameters
[in]N
          N is INTEGER
          The order of the matrix A.
[in,out]DL
          DL is DOUBLE PRECISION array, dimension (N-1)
          On entry, DL must contain the (n-1) sub-diagonal elements of
          A.

          On exit, DL is overwritten by the (n-1) multipliers that
          define the matrix L from the LU factorization of A.
[in,out]D
          D is DOUBLE PRECISION array, dimension (N)
          On entry, D must contain the diagonal elements of A.

          On exit, D is overwritten by the n diagonal elements of the
          upper triangular matrix U from the LU factorization of A.
[in,out]DU
          DU is DOUBLE PRECISION array, dimension (N-1)
          On entry, DU must contain the (n-1) super-diagonal elements
          of A.

          On exit, DU is overwritten by the (n-1) elements of the first
          super-diagonal of U.
[out]DU2
          DU2 is DOUBLE PRECISION array, dimension (N-2)
          On exit, DU2 is overwritten by the (n-2) elements of the
          second super-diagonal of U.
[out]IPIV
          IPIV is INTEGER array, dimension (N)
          The pivot indices; for 1 <= i <= n, row i of the matrix was
          interchanged with row IPIV(i).  IPIV(i) will always be either
          i or i+1; IPIV(i) = i indicates a row interchange was not
          required.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -k, the k-th argument had an illegal value
          > 0:  if INFO = k, U(k,k) is exactly zero. The factorization
                has been completed, but the factor U is exactly
                singular, and division by zero will occur if it is used
                to solve a system of equations.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012

Definition at line 126 of file dgttrf.f.

126 *
127 * -- LAPACK computational routine (version 3.4.2) --
128 * -- LAPACK is a software package provided by Univ. of Tennessee, --
129 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
130 * September 2012
131 *
132 * .. Scalar Arguments ..
133  INTEGER info, n
134 * ..
135 * .. Array Arguments ..
136  INTEGER ipiv( * )
137  DOUBLE PRECISION d( * ), dl( * ), du( * ), du2( * )
138 * ..
139 *
140 * =====================================================================
141 *
142 * .. Parameters ..
143  DOUBLE PRECISION zero
144  parameter ( zero = 0.0d+0 )
145 * ..
146 * .. Local Scalars ..
147  INTEGER i
148  DOUBLE PRECISION fact, temp
149 * ..
150 * .. Intrinsic Functions ..
151  INTRINSIC abs
152 * ..
153 * .. External Subroutines ..
154  EXTERNAL xerbla
155 * ..
156 * .. Executable Statements ..
157 *
158  info = 0
159  IF( n.LT.0 ) THEN
160  info = -1
161  CALL xerbla( 'DGTTRF', -info )
162  RETURN
163  END IF
164 *
165 * Quick return if possible
166 *
167  IF( n.EQ.0 )
168  $ RETURN
169 *
170 * Initialize IPIV(i) = i and DU2(I) = 0
171 *
172  DO 10 i = 1, n
173  ipiv( i ) = i
174  10 CONTINUE
175  DO 20 i = 1, n - 2
176  du2( i ) = zero
177  20 CONTINUE
178 *
179  DO 30 i = 1, n - 2
180  IF( abs( d( i ) ).GE.abs( dl( i ) ) ) THEN
181 *
182 * No row interchange required, eliminate DL(I)
183 *
184  IF( d( i ).NE.zero ) THEN
185  fact = dl( i ) / d( i )
186  dl( i ) = fact
187  d( i+1 ) = d( i+1 ) - fact*du( i )
188  END IF
189  ELSE
190 *
191 * Interchange rows I and I+1, eliminate DL(I)
192 *
193  fact = d( i ) / dl( i )
194  d( i ) = dl( i )
195  dl( i ) = fact
196  temp = du( i )
197  du( i ) = d( i+1 )
198  d( i+1 ) = temp - fact*d( i+1 )
199  du2( i ) = du( i+1 )
200  du( i+1 ) = -fact*du( i+1 )
201  ipiv( i ) = i + 1
202  END IF
203  30 CONTINUE
204  IF( n.GT.1 ) THEN
205  i = n - 1
206  IF( abs( d( i ) ).GE.abs( dl( i ) ) ) THEN
207  IF( d( i ).NE.zero ) THEN
208  fact = dl( i ) / d( i )
209  dl( i ) = fact
210  d( i+1 ) = d( i+1 ) - fact*du( i )
211  END IF
212  ELSE
213  fact = d( i ) / dl( i )
214  d( i ) = dl( i )
215  dl( i ) = fact
216  temp = du( i )
217  du( i ) = d( i+1 )
218  d( i+1 ) = temp - fact*d( i+1 )
219  ipiv( i ) = i + 1
220  END IF
221  END IF
222 *
223 * Check for a zero on the diagonal of U.
224 *
225  DO 40 i = 1, n
226  IF( d( i ).EQ.zero ) THEN
227  info = i
228  GO TO 50
229  END IF
230  40 CONTINUE
231  50 CONTINUE
232 *
233  RETURN
234 *
235 * End of DGTTRF
236 *
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: