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

◆ zpttrf()

subroutine zpttrf ( integer n,
double precision, dimension( * ) d,
complex*16, dimension( * ) e,
integer info )

ZPTTRF

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

Purpose:
!>
!> ZPTTRF computes the L*D*L**H factorization of a complex Hermitian
!> positive definite tridiagonal matrix A.  The factorization may also
!> be regarded as having the form A = U**H *D*U.
!> 
Parameters
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in,out]D
!>          D is DOUBLE PRECISION array, dimension (N)
!>          On entry, the n diagonal elements of the tridiagonal matrix
!>          A.  On exit, the n diagonal elements of the diagonal matrix
!>          D from the L*D*L**H factorization of A.
!> 
[in,out]E
!>          E is COMPLEX*16 array, dimension (N-1)
!>          On entry, the (n-1) subdiagonal elements of the tridiagonal
!>          matrix A.  On exit, the (n-1) subdiagonal elements of the
!>          unit bidiagonal factor L from the L*D*L**H factorization of A.
!>          E can also be regarded as the superdiagonal of the unit
!>          bidiagonal factor U from the U**H *D*U factorization of A.
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0: successful exit
!>          < 0: if INFO = -k, the k-th argument had an illegal value
!>          > 0: if INFO = k, the leading principal minor of order k
!>               is not positive; if k < N, the factorization could not
!>               be completed, while if k = N, the factorization was
!>               completed, but D(N) <= 0.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 89 of file zpttrf.f.

90*
91* -- LAPACK computational routine --
92* -- LAPACK is a software package provided by Univ. of Tennessee, --
93* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
94*
95* .. Scalar Arguments ..
96 INTEGER INFO, N
97* ..
98* .. Array Arguments ..
99 DOUBLE PRECISION D( * )
100 COMPLEX*16 E( * )
101* ..
102*
103* =====================================================================
104*
105* .. Parameters ..
106 DOUBLE PRECISION ZERO
107 parameter( zero = 0.0d+0 )
108* ..
109* .. Local Scalars ..
110 INTEGER I, I4
111 DOUBLE PRECISION EII, EIR, F, G
112* ..
113* .. External Subroutines ..
114 EXTERNAL xerbla
115* ..
116* .. Intrinsic Functions ..
117 INTRINSIC dble, dcmplx, dimag, mod
118* ..
119* .. Executable Statements ..
120*
121* Test the input parameters.
122*
123 info = 0
124 IF( n.LT.0 ) THEN
125 info = -1
126 CALL xerbla( 'ZPTTRF', -info )
127 RETURN
128 END IF
129*
130* Quick return if possible
131*
132 IF( n.EQ.0 )
133 $ RETURN
134*
135* Compute the L*D*L**H (or U**H *D*U) factorization of A.
136*
137 i4 = mod( n-1, 4 )
138 DO 10 i = 1, i4
139 IF( d( i ).LE.zero ) THEN
140 info = i
141 GO TO 30
142 END IF
143 eir = dble( e( i ) )
144 eii = dimag( e( i ) )
145 f = eir / d( i )
146 g = eii / d( i )
147 e( i ) = dcmplx( f, g )
148 d( i+1 ) = d( i+1 ) - f*eir - g*eii
149 10 CONTINUE
150*
151 DO 20 i = i4 + 1, n - 4, 4
152*
153* Drop out of the loop if d(i) <= 0: the matrix is not positive
154* definite.
155*
156 IF( d( i ).LE.zero ) THEN
157 info = i
158 GO TO 30
159 END IF
160*
161* Solve for e(i) and d(i+1).
162*
163 eir = dble( e( i ) )
164 eii = dimag( e( i ) )
165 f = eir / d( i )
166 g = eii / d( i )
167 e( i ) = dcmplx( f, g )
168 d( i+1 ) = d( i+1 ) - f*eir - g*eii
169*
170 IF( d( i+1 ).LE.zero ) THEN
171 info = i + 1
172 GO TO 30
173 END IF
174*
175* Solve for e(i+1) and d(i+2).
176*
177 eir = dble( e( i+1 ) )
178 eii = dimag( e( i+1 ) )
179 f = eir / d( i+1 )
180 g = eii / d( i+1 )
181 e( i+1 ) = dcmplx( f, g )
182 d( i+2 ) = d( i+2 ) - f*eir - g*eii
183*
184 IF( d( i+2 ).LE.zero ) THEN
185 info = i + 2
186 GO TO 30
187 END IF
188*
189* Solve for e(i+2) and d(i+3).
190*
191 eir = dble( e( i+2 ) )
192 eii = dimag( e( i+2 ) )
193 f = eir / d( i+2 )
194 g = eii / d( i+2 )
195 e( i+2 ) = dcmplx( f, g )
196 d( i+3 ) = d( i+3 ) - f*eir - g*eii
197*
198 IF( d( i+3 ).LE.zero ) THEN
199 info = i + 3
200 GO TO 30
201 END IF
202*
203* Solve for e(i+3) and d(i+4).
204*
205 eir = dble( e( i+3 ) )
206 eii = dimag( e( i+3 ) )
207 f = eir / d( i+3 )
208 g = eii / d( i+3 )
209 e( i+3 ) = dcmplx( f, g )
210 d( i+4 ) = d( i+4 ) - f*eir - g*eii
211 20 CONTINUE
212*
213* Check d(n) for positive definiteness.
214*
215 IF( d( n ).LE.zero )
216 $ info = n
217*
218 30 CONTINUE
219 RETURN
220*
221* End of ZPTTRF
222*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
Here is the call graph for this function:
Here is the caller graph for this function: