LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cgttrf.f
Go to the documentation of this file.
1*> \brief \b CGTTRF
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CGTTRF + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgttrf.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgttrf.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgttrf.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CGTTRF( N, DL, D, DU, DU2, IPIV, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, N
23* ..
24* .. Array Arguments ..
25* INTEGER IPIV( * )
26* COMPLEX D( * ), DL( * ), DU( * ), DU2( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CGTTRF computes an LU factorization of a complex tridiagonal matrix A
36*> using elimination with partial pivoting and row interchanges.
37*>
38*> The factorization has the form
39*> A = L * U
40*> where L is a product of permutation and unit lower bidiagonal
41*> matrices and U is upper triangular with nonzeros in only the main
42*> diagonal and first two superdiagonals.
43*> \endverbatim
44*
45* Arguments:
46* ==========
47*
48*> \param[in] N
49*> \verbatim
50*> N is INTEGER
51*> The order of the matrix A.
52*> \endverbatim
53*>
54*> \param[in,out] DL
55*> \verbatim
56*> DL is COMPLEX array, dimension (N-1)
57*> On entry, DL must contain the (n-1) sub-diagonal elements of
58*> A.
59*>
60*> On exit, DL is overwritten by the (n-1) multipliers that
61*> define the matrix L from the LU factorization of A.
62*> \endverbatim
63*>
64*> \param[in,out] D
65*> \verbatim
66*> D is COMPLEX array, dimension (N)
67*> On entry, D must contain the diagonal elements of A.
68*>
69*> On exit, D is overwritten by the n diagonal elements of the
70*> upper triangular matrix U from the LU factorization of A.
71*> \endverbatim
72*>
73*> \param[in,out] DU
74*> \verbatim
75*> DU is COMPLEX array, dimension (N-1)
76*> On entry, DU must contain the (n-1) super-diagonal elements
77*> of A.
78*>
79*> On exit, DU is overwritten by the (n-1) elements of the first
80*> super-diagonal of U.
81*> \endverbatim
82*>
83*> \param[out] DU2
84*> \verbatim
85*> DU2 is COMPLEX array, dimension (N-2)
86*> On exit, DU2 is overwritten by the (n-2) elements of the
87*> second super-diagonal of U.
88*> \endverbatim
89*>
90*> \param[out] IPIV
91*> \verbatim
92*> IPIV is INTEGER array, dimension (N)
93*> The pivot indices; for 1 <= i <= n, row i of the matrix was
94*> interchanged with row IPIV(i). IPIV(i) will always be either
95*> i or i+1; IPIV(i) = i indicates a row interchange was not
96*> required.
97*> \endverbatim
98*>
99*> \param[out] INFO
100*> \verbatim
101*> INFO is INTEGER
102*> = 0: successful exit
103*> < 0: if INFO = -k, the k-th argument had an illegal value
104*> > 0: if INFO = k, U(k,k) is exactly zero. The factorization
105*> has been completed, but the factor U is exactly
106*> singular, and division by zero will occur if it is used
107*> to solve a system of equations.
108*> \endverbatim
109*
110* Authors:
111* ========
112*
113*> \author Univ. of Tennessee
114*> \author Univ. of California Berkeley
115*> \author Univ. of Colorado Denver
116*> \author NAG Ltd.
117*
118*> \ingroup gttrf
119*
120* =====================================================================
121 SUBROUTINE cgttrf( N, DL, D, DU, DU2, IPIV, INFO )
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 COMPLEX 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 COMPLEX FACT, TEMP, ZDUM
144* ..
145* .. External Subroutines ..
146 EXTERNAL xerbla
147* ..
148* .. Intrinsic Functions ..
149 INTRINSIC abs, aimag, real
150* ..
151* .. Statement Functions ..
152 REAL CABS1
153* ..
154* .. Statement Function definitions ..
155 cabs1( zdum ) = abs( real( zdum ) ) + abs( aimag( zdum ) )
156* ..
157* .. Executable Statements ..
158*
159 info = 0
160 IF( n.LT.0 ) THEN
161 info = -1
162 CALL xerbla( 'CGTTRF', -info )
163 RETURN
164 END IF
165*
166* Quick return if possible
167*
168 IF( n.EQ.0 )
169 $ RETURN
170*
171* Initialize IPIV(i) = i and DU2(i) = 0
172*
173 DO 10 i = 1, n
174 ipiv( i ) = i
175 10 CONTINUE
176 DO 20 i = 1, n - 2
177 du2( i ) = zero
178 20 CONTINUE
179*
180 DO 30 i = 1, n - 2
181 IF( cabs1( d( i ) ).GE.cabs1( dl( i ) ) ) THEN
182*
183* No row interchange required, eliminate DL(I)
184*
185 IF( cabs1( d( i ) ).NE.zero ) THEN
186 fact = dl( i ) / d( i )
187 dl( i ) = fact
188 d( i+1 ) = d( i+1 ) - fact*du( i )
189 END IF
190 ELSE
191*
192* Interchange rows I and I+1, eliminate DL(I)
193*
194 fact = d( i ) / dl( i )
195 d( i ) = dl( i )
196 dl( i ) = fact
197 temp = du( i )
198 du( i ) = d( i+1 )
199 d( i+1 ) = temp - fact*d( i+1 )
200 du2( i ) = du( i+1 )
201 du( i+1 ) = -fact*du( i+1 )
202 ipiv( i ) = i + 1
203 END IF
204 30 CONTINUE
205 IF( n.GT.1 ) THEN
206 i = n - 1
207 IF( cabs1( d( i ) ).GE.cabs1( dl( i ) ) ) THEN
208 IF( cabs1( d( i ) ).NE.zero ) THEN
209 fact = dl( i ) / d( i )
210 dl( i ) = fact
211 d( i+1 ) = d( i+1 ) - fact*du( i )
212 END IF
213 ELSE
214 fact = d( i ) / dl( i )
215 d( i ) = dl( i )
216 dl( i ) = fact
217 temp = du( i )
218 du( i ) = d( i+1 )
219 d( i+1 ) = temp - fact*d( i+1 )
220 ipiv( i ) = i + 1
221 END IF
222 END IF
223*
224* Check for a zero on the diagonal of U.
225*
226 DO 40 i = 1, n
227 IF( cabs1( d( i ) ).EQ.zero ) THEN
228 info = i
229 GO TO 50
230 END IF
231 40 CONTINUE
232 50 CONTINUE
233*
234 RETURN
235*
236* End of CGTTRF
237*
238 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cgttrf(n, dl, d, du, du2, ipiv, info)
CGTTRF
Definition cgttrf.f:122