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

◆ sgttrf()

subroutine sgttrf ( integer n,
real, dimension( * ) dl,
real, dimension( * ) d,
real, dimension( * ) du,
real, dimension( * ) du2,
integer, dimension( * ) ipiv,
integer info )

SGTTRF

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

Purpose:
!>
!> SGTTRF 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 REAL 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 REAL 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 REAL 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 REAL 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.

Definition at line 121 of file sgttrf.f.

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