LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages
cpbstf.f
Go to the documentation of this file.
1*> \brief \b CPBSTF
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CPBSTF + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cpbstf.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cpbstf.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cpbstf.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CPBSTF( UPLO, N, KD, AB, LDAB, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, KD, LDAB, N
24* ..
25* .. Array Arguments ..
26* COMPLEX AB( LDAB, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CPBSTF computes a split Cholesky factorization of a complex
36*> Hermitian positive definite band matrix A.
37*>
38*> This routine is designed to be used in conjunction with CHBGST.
39*>
40*> The factorization has the form A = S**H*S where S is a band matrix
41*> of the same bandwidth as A and the following structure:
42*>
43*> S = ( U )
44*> ( M L )
45*>
46*> where U is upper triangular of order m = (n+kd)/2, and L is lower
47*> triangular of order n-m.
48*> \endverbatim
49*
50* Arguments:
51* ==========
52*
53*> \param[in] UPLO
54*> \verbatim
55*> UPLO is CHARACTER*1
56*> = 'U': Upper triangle of A is stored;
57*> = 'L': Lower triangle of A is stored.
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*> N is INTEGER
63*> The order of the matrix A. N >= 0.
64*> \endverbatim
65*>
66*> \param[in] KD
67*> \verbatim
68*> KD is INTEGER
69*> The number of superdiagonals of the matrix A if UPLO = 'U',
70*> or the number of subdiagonals if UPLO = 'L'. KD >= 0.
71*> \endverbatim
72*>
73*> \param[in,out] AB
74*> \verbatim
75*> AB is COMPLEX array, dimension (LDAB,N)
76*> On entry, the upper or lower triangle of the Hermitian band
77*> matrix A, stored in the first kd+1 rows of the array. The
78*> j-th column of A is stored in the j-th column of the array AB
79*> as follows:
80*> if UPLO = 'U', AB(kd+1+i-j,j) = A(i,j) for max(1,j-kd)<=i<=j;
81*> if UPLO = 'L', AB(1+i-j,j) = A(i,j) for j<=i<=min(n,j+kd).
82*>
83*> On exit, if INFO = 0, the factor S from the split Cholesky
84*> factorization A = S**H*S. See Further Details.
85*> \endverbatim
86*>
87*> \param[in] LDAB
88*> \verbatim
89*> LDAB is INTEGER
90*> The leading dimension of the array AB. LDAB >= KD+1.
91*> \endverbatim
92*>
93*> \param[out] INFO
94*> \verbatim
95*> INFO is INTEGER
96*> = 0: successful exit
97*> < 0: if INFO = -i, the i-th argument had an illegal value
98*> > 0: if INFO = i, the factorization could not be completed,
99*> because the updated element a(i,i) was negative; the
100*> matrix A is not positive definite.
101*> \endverbatim
102*
103* Authors:
104* ========
105*
106*> \author Univ. of Tennessee
107*> \author Univ. of California Berkeley
108*> \author Univ. of Colorado Denver
109*> \author NAG Ltd.
110*
111*> \ingroup pbstf
112*
113*> \par Further Details:
114* =====================
115*>
116*> \verbatim
117*>
118*> The band storage scheme is illustrated by the following example, when
119*> N = 7, KD = 2:
120*>
121*> S = ( s11 s12 s13 )
122*> ( s22 s23 s24 )
123*> ( s33 s34 )
124*> ( s44 )
125*> ( s53 s54 s55 )
126*> ( s64 s65 s66 )
127*> ( s75 s76 s77 )
128*>
129*> If UPLO = 'U', the array AB holds:
130*>
131*> on entry: on exit:
132*>
133*> * * a13 a24 a35 a46 a57 * * s13 s24 s53**H s64**H s75**H
134*> * a12 a23 a34 a45 a56 a67 * s12 s23 s34 s54**H s65**H s76**H
135*> a11 a22 a33 a44 a55 a66 a77 s11 s22 s33 s44 s55 s66 s77
136*>
137*> If UPLO = 'L', the array AB holds:
138*>
139*> on entry: on exit:
140*>
141*> a11 a22 a33 a44 a55 a66 a77 s11 s22 s33 s44 s55 s66 s77
142*> a21 a32 a43 a54 a65 a76 * s12**H s23**H s34**H s54 s65 s76 *
143*> a31 a42 a53 a64 a64 * * s13**H s24**H s53 s64 s75 * *
144*>
145*> Array elements marked * are not used by the routine; s12**H denotes
146*> conjg(s12); the diagonal elements of S are real.
147*> \endverbatim
148*>
149* =====================================================================
150 SUBROUTINE cpbstf( UPLO, N, KD, AB, LDAB, INFO )
151*
152* -- LAPACK computational routine --
153* -- LAPACK is a software package provided by Univ. of Tennessee, --
154* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
155*
156* .. Scalar Arguments ..
157 CHARACTER UPLO
158 INTEGER INFO, KD, LDAB, N
159* ..
160* .. Array Arguments ..
161 COMPLEX AB( LDAB, * )
162* ..
163*
164* =====================================================================
165*
166* .. Parameters ..
167 REAL ONE, ZERO
168 parameter( one = 1.0e+0, zero = 0.0e+0 )
169* ..
170* .. Local Scalars ..
171 LOGICAL UPPER
172 INTEGER J, KLD, KM, M
173 REAL AJJ
174* ..
175* .. External Functions ..
176 LOGICAL LSAME
177 EXTERNAL lsame
178* ..
179* .. External Subroutines ..
180 EXTERNAL cher, clacgv, csscal, xerbla
181* ..
182* .. Intrinsic Functions ..
183 INTRINSIC max, min, real, sqrt
184* ..
185* .. Executable Statements ..
186*
187* Test the input parameters.
188*
189 info = 0
190 upper = lsame( uplo, 'U' )
191 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
192 info = -1
193 ELSE IF( n.LT.0 ) THEN
194 info = -2
195 ELSE IF( kd.LT.0 ) THEN
196 info = -3
197 ELSE IF( ldab.LT.kd+1 ) THEN
198 info = -5
199 END IF
200 IF( info.NE.0 ) THEN
201 CALL xerbla( 'CPBSTF', -info )
202 RETURN
203 END IF
204*
205* Quick return if possible
206*
207 IF( n.EQ.0 )
208 $ RETURN
209*
210 kld = max( 1, ldab-1 )
211*
212* Set the splitting point m.
213*
214 m = ( n+kd ) / 2
215*
216 IF( upper ) THEN
217*
218* Factorize A(m+1:n,m+1:n) as L**H*L, and update A(1:m,1:m).
219*
220 DO 10 j = n, m + 1, -1
221*
222* Compute s(j,j) and test for non-positive-definiteness.
223*
224 ajj = real( ab( kd+1, j ) )
225 IF( ajj.LE.zero ) THEN
226 ab( kd+1, j ) = ajj
227 GO TO 50
228 END IF
229 ajj = sqrt( ajj )
230 ab( kd+1, j ) = ajj
231 km = min( j-1, kd )
232*
233* Compute elements j-km:j-1 of the j-th column and update the
234* the leading submatrix within the band.
235*
236 CALL csscal( km, one / ajj, ab( kd+1-km, j ), 1 )
237 CALL cher( 'Upper', km, -one, ab( kd+1-km, j ), 1,
238 $ ab( kd+1, j-km ), kld )
239 10 CONTINUE
240*
241* Factorize the updated submatrix A(1:m,1:m) as U**H*U.
242*
243 DO 20 j = 1, m
244*
245* Compute s(j,j) and test for non-positive-definiteness.
246*
247 ajj = real( ab( kd+1, j ) )
248 IF( ajj.LE.zero ) THEN
249 ab( kd+1, j ) = ajj
250 GO TO 50
251 END IF
252 ajj = sqrt( ajj )
253 ab( kd+1, j ) = ajj
254 km = min( kd, m-j )
255*
256* Compute elements j+1:j+km of the j-th row and update the
257* trailing submatrix within the band.
258*
259 IF( km.GT.0 ) THEN
260 CALL csscal( km, one / ajj, ab( kd, j+1 ), kld )
261 CALL clacgv( km, ab( kd, j+1 ), kld )
262 CALL cher( 'Upper', km, -one, ab( kd, j+1 ), kld,
263 $ ab( kd+1, j+1 ), kld )
264 CALL clacgv( km, ab( kd, j+1 ), kld )
265 END IF
266 20 CONTINUE
267 ELSE
268*
269* Factorize A(m+1:n,m+1:n) as L**H*L, and update A(1:m,1:m).
270*
271 DO 30 j = n, m + 1, -1
272*
273* Compute s(j,j) and test for non-positive-definiteness.
274*
275 ajj = real( ab( 1, j ) )
276 IF( ajj.LE.zero ) THEN
277 ab( 1, j ) = ajj
278 GO TO 50
279 END IF
280 ajj = sqrt( ajj )
281 ab( 1, j ) = ajj
282 km = min( j-1, kd )
283*
284* Compute elements j-km:j-1 of the j-th row and update the
285* trailing submatrix within the band.
286*
287 CALL csscal( km, one / ajj, ab( km+1, j-km ), kld )
288 CALL clacgv( km, ab( km+1, j-km ), kld )
289 CALL cher( 'Lower', km, -one, ab( km+1, j-km ), kld,
290 $ ab( 1, j-km ), kld )
291 CALL clacgv( km, ab( km+1, j-km ), kld )
292 30 CONTINUE
293*
294* Factorize the updated submatrix A(1:m,1:m) as U**H*U.
295*
296 DO 40 j = 1, m
297*
298* Compute s(j,j) and test for non-positive-definiteness.
299*
300 ajj = real( ab( 1, j ) )
301 IF( ajj.LE.zero ) THEN
302 ab( 1, j ) = ajj
303 GO TO 50
304 END IF
305 ajj = sqrt( ajj )
306 ab( 1, j ) = ajj
307 km = min( kd, m-j )
308*
309* Compute elements j+1:j+km of the j-th column and update the
310* trailing submatrix within the band.
311*
312 IF( km.GT.0 ) THEN
313 CALL csscal( km, one / ajj, ab( 2, j ), 1 )
314 CALL cher( 'Lower', km, -one, ab( 2, j ), 1,
315 $ ab( 1, j+1 ), kld )
316 END IF
317 40 CONTINUE
318 END IF
319 RETURN
320*
321 50 CONTINUE
322 info = j
323 RETURN
324*
325* End of CPBSTF
326*
327 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine cher(uplo, n, alpha, x, incx, a, lda)
CHER
Definition cher.f:135
subroutine clacgv(n, x, incx)
CLACGV conjugates a complex vector.
Definition clacgv.f:72
subroutine cpbstf(uplo, n, kd, ab, ldab, info)
CPBSTF
Definition cpbstf.f:151
subroutine csscal(n, sa, cx, incx)
CSSCAL
Definition csscal.f:78