LAPACK 3.12.0
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 123 of file sgttrf.f.

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