LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dpttrf.f
Go to the documentation of this file.
1*> \brief \b DPTTRF
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DPTTRF + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dpttrf.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dpttrf.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dpttrf.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DPTTRF( N, D, E, INFO )
20*
21* .. Scalar Arguments ..
22* INTEGER INFO, N
23* ..
24* .. Array Arguments ..
25* DOUBLE PRECISION D( * ), E( * )
26* ..
27*
28*
29*> \par Purpose:
30* =============
31*>
32*> \verbatim
33*>
34*> DPTTRF computes the L*D*L**T factorization of a real symmetric
35*> positive definite tridiagonal matrix A. The factorization may also
36*> be regarded as having the form A = U**T*D*U.
37*> \endverbatim
38*
39* Arguments:
40* ==========
41*
42*> \param[in] N
43*> \verbatim
44*> N is INTEGER
45*> The order of the matrix A. N >= 0.
46*> \endverbatim
47*>
48*> \param[in,out] D
49*> \verbatim
50*> D is DOUBLE PRECISION array, dimension (N)
51*> On entry, the n diagonal elements of the tridiagonal matrix
52*> A. On exit, the n diagonal elements of the diagonal matrix
53*> D from the L*D*L**T factorization of A.
54*> \endverbatim
55*>
56*> \param[in,out] E
57*> \verbatim
58*> E is DOUBLE PRECISION array, dimension (N-1)
59*> On entry, the (n-1) subdiagonal elements of the tridiagonal
60*> matrix A. On exit, the (n-1) subdiagonal elements of the
61*> unit bidiagonal factor L from the L*D*L**T factorization of A.
62*> E can also be regarded as the superdiagonal of the unit
63*> bidiagonal factor U from the U**T*D*U factorization of A.
64*> \endverbatim
65*>
66*> \param[out] INFO
67*> \verbatim
68*> INFO is INTEGER
69*> = 0: successful exit
70*> < 0: if INFO = -k, the k-th argument had an illegal value
71*> > 0: if INFO = k, the leading principal minor of order k
72*> is not positive; if k < N, the factorization could not
73*> be completed, while if k = N, the factorization was
74*> completed, but D(N) <= 0.
75*> \endverbatim
76*
77* Authors:
78* ========
79*
80*> \author Univ. of Tennessee
81*> \author Univ. of California Berkeley
82*> \author Univ. of Colorado Denver
83*> \author NAG Ltd.
84*
85*> \ingroup pttrf
86*
87* =====================================================================
88 SUBROUTINE dpttrf( N, D, E, INFO )
89*
90* -- LAPACK computational routine --
91* -- LAPACK is a software package provided by Univ. of Tennessee, --
92* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
93*
94* .. Scalar Arguments ..
95 INTEGER INFO, N
96* ..
97* .. Array Arguments ..
98 DOUBLE PRECISION D( * ), E( * )
99* ..
100*
101* =====================================================================
102*
103* .. Parameters ..
104 DOUBLE PRECISION ZERO
105 parameter( zero = 0.0d+0 )
106* ..
107* .. Local Scalars ..
108 INTEGER I, I4
109 DOUBLE PRECISION EI
110* ..
111* .. External Subroutines ..
112 EXTERNAL xerbla
113* ..
114* .. Intrinsic Functions ..
115 INTRINSIC mod
116* ..
117* .. Executable Statements ..
118*
119* Test the input parameters.
120*
121 info = 0
122 IF( n.LT.0 ) THEN
123 info = -1
124 CALL xerbla( 'DPTTRF', -info )
125 RETURN
126 END IF
127*
128* Quick return if possible
129*
130 IF( n.EQ.0 )
131 $ RETURN
132*
133* Compute the L*D*L**T (or U**T*D*U) factorization of A.
134*
135 i4 = mod( n-1, 4 )
136 DO 10 i = 1, i4
137 IF( d( i ).LE.zero ) THEN
138 info = i
139 GO TO 30
140 END IF
141 ei = e( i )
142 e( i ) = ei / d( i )
143 d( i+1 ) = d( i+1 ) - e( i )*ei
144 10 CONTINUE
145*
146 DO 20 i = i4 + 1, n - 4, 4
147*
148* Drop out of the loop if d(i) <= 0: the matrix is not positive
149* definite.
150*
151 IF( d( i ).LE.zero ) THEN
152 info = i
153 GO TO 30
154 END IF
155*
156* Solve for e(i) and d(i+1).
157*
158 ei = e( i )
159 e( i ) = ei / d( i )
160 d( i+1 ) = d( i+1 ) - e( i )*ei
161*
162 IF( d( i+1 ).LE.zero ) THEN
163 info = i + 1
164 GO TO 30
165 END IF
166*
167* Solve for e(i+1) and d(i+2).
168*
169 ei = e( i+1 )
170 e( i+1 ) = ei / d( i+1 )
171 d( i+2 ) = d( i+2 ) - e( i+1 )*ei
172*
173 IF( d( i+2 ).LE.zero ) THEN
174 info = i + 2
175 GO TO 30
176 END IF
177*
178* Solve for e(i+2) and d(i+3).
179*
180 ei = e( i+2 )
181 e( i+2 ) = ei / d( i+2 )
182 d( i+3 ) = d( i+3 ) - e( i+2 )*ei
183*
184 IF( d( i+3 ).LE.zero ) THEN
185 info = i + 3
186 GO TO 30
187 END IF
188*
189* Solve for e(i+3) and d(i+4).
190*
191 ei = e( i+3 )
192 e( i+3 ) = ei / d( i+3 )
193 d( i+4 ) = d( i+4 ) - e( i+3 )*ei
194 20 CONTINUE
195*
196* Check d(n) for positive definiteness.
197*
198 IF( d( n ).LE.zero )
199 $ info = n
200*
201 30 CONTINUE
202 RETURN
203*
204* End of DPTTRF
205*
206 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dpttrf(n, d, e, info)
DPTTRF
Definition dpttrf.f:89