LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
spbstf.f
Go to the documentation of this file.
1*> \brief \b SPBSTF
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download SPBSTF + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/spbstf.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/spbstf.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/spbstf.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE SPBSTF( UPLO, N, KD, AB, LDAB, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, KD, LDAB, N
24* ..
25* .. Array Arguments ..
26* REAL AB( LDAB, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> SPBSTF computes a split Cholesky factorization of a real
36*> symmetric positive definite band matrix A.
37*>
38*> This routine is designed to be used in conjunction with SSBGST.
39*>
40*> The factorization has the form A = S**T*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 REAL array, dimension (LDAB,N)
76*> On entry, the upper or lower triangle of the symmetric 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**T*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 s64 s75
134*> * a12 a23 a34 a45 a56 a67 * s12 s23 s34 s54 s65 s76
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 s23 s34 s54 s65 s76 *
143*> a31 a42 a53 a64 a64 * * s13 s24 s53 s64 s75 * *
144*>
145*> Array elements marked * are not used by the routine.
146*> \endverbatim
147*>
148* =====================================================================
149 SUBROUTINE spbstf( UPLO, N, KD, AB, LDAB, INFO )
150*
151* -- LAPACK computational routine --
152* -- LAPACK is a software package provided by Univ. of Tennessee, --
153* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
154*
155* .. Scalar Arguments ..
156 CHARACTER UPLO
157 INTEGER INFO, KD, LDAB, N
158* ..
159* .. Array Arguments ..
160 REAL AB( LDAB, * )
161* ..
162*
163* =====================================================================
164*
165* .. Parameters ..
166 REAL ONE, ZERO
167 parameter( one = 1.0e+0, zero = 0.0e+0 )
168* ..
169* .. Local Scalars ..
170 LOGICAL UPPER
171 INTEGER J, KLD, KM, M
172 REAL AJJ
173* ..
174* .. External Functions ..
175 LOGICAL LSAME
176 EXTERNAL lsame
177* ..
178* .. External Subroutines ..
179 EXTERNAL sscal, ssyr, xerbla
180* ..
181* .. Intrinsic Functions ..
182 INTRINSIC max, min, sqrt
183* ..
184* .. Executable Statements ..
185*
186* Test the input parameters.
187*
188 info = 0
189 upper = lsame( uplo, 'U' )
190 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
191 info = -1
192 ELSE IF( n.LT.0 ) THEN
193 info = -2
194 ELSE IF( kd.LT.0 ) THEN
195 info = -3
196 ELSE IF( ldab.LT.kd+1 ) THEN
197 info = -5
198 END IF
199 IF( info.NE.0 ) THEN
200 CALL xerbla( 'SPBSTF', -info )
201 RETURN
202 END IF
203*
204* Quick return if possible
205*
206 IF( n.EQ.0 )
207 $ RETURN
208*
209 kld = max( 1, ldab-1 )
210*
211* Set the splitting point m.
212*
213 m = ( n+kd ) / 2
214*
215 IF( upper ) THEN
216*
217* Factorize A(m+1:n,m+1:n) as L**T*L, and update A(1:m,1:m).
218*
219 DO 10 j = n, m + 1, -1
220*
221* Compute s(j,j) and test for non-positive-definiteness.
222*
223 ajj = ab( kd+1, j )
224 IF( ajj.LE.zero )
225 $ GO TO 50
226 ajj = sqrt( ajj )
227 ab( kd+1, j ) = ajj
228 km = min( j-1, kd )
229*
230* Compute elements j-km:j-1 of the j-th column and update the
231* the leading submatrix within the band.
232*
233 CALL sscal( km, one / ajj, ab( kd+1-km, j ), 1 )
234 CALL ssyr( 'Upper', km, -one, ab( kd+1-km, j ), 1,
235 $ ab( kd+1, j-km ), kld )
236 10 CONTINUE
237*
238* Factorize the updated submatrix A(1:m,1:m) as U**T*U.
239*
240 DO 20 j = 1, m
241*
242* Compute s(j,j) and test for non-positive-definiteness.
243*
244 ajj = ab( kd+1, j )
245 IF( ajj.LE.zero )
246 $ GO TO 50
247 ajj = sqrt( ajj )
248 ab( kd+1, j ) = ajj
249 km = min( kd, m-j )
250*
251* Compute elements j+1:j+km of the j-th row and update the
252* trailing submatrix within the band.
253*
254 IF( km.GT.0 ) THEN
255 CALL sscal( km, one / ajj, ab( kd, j+1 ), kld )
256 CALL ssyr( 'Upper', km, -one, ab( kd, j+1 ), kld,
257 $ ab( kd+1, j+1 ), kld )
258 END IF
259 20 CONTINUE
260 ELSE
261*
262* Factorize A(m+1:n,m+1:n) as L**T*L, and update A(1:m,1:m).
263*
264 DO 30 j = n, m + 1, -1
265*
266* Compute s(j,j) and test for non-positive-definiteness.
267*
268 ajj = ab( 1, j )
269 IF( ajj.LE.zero )
270 $ GO TO 50
271 ajj = sqrt( ajj )
272 ab( 1, j ) = ajj
273 km = min( j-1, kd )
274*
275* Compute elements j-km:j-1 of the j-th row and update the
276* trailing submatrix within the band.
277*
278 CALL sscal( km, one / ajj, ab( km+1, j-km ), kld )
279 CALL ssyr( 'Lower', km, -one, ab( km+1, j-km ), kld,
280 $ ab( 1, j-km ), kld )
281 30 CONTINUE
282*
283* Factorize the updated submatrix A(1:m,1:m) as U**T*U.
284*
285 DO 40 j = 1, m
286*
287* Compute s(j,j) and test for non-positive-definiteness.
288*
289 ajj = ab( 1, j )
290 IF( ajj.LE.zero )
291 $ GO TO 50
292 ajj = sqrt( ajj )
293 ab( 1, j ) = ajj
294 km = min( kd, m-j )
295*
296* Compute elements j+1:j+km of the j-th column and update the
297* trailing submatrix within the band.
298*
299 IF( km.GT.0 ) THEN
300 CALL sscal( km, one / ajj, ab( 2, j ), 1 )
301 CALL ssyr( 'Lower', km, -one, ab( 2, j ), 1,
302 $ ab( 1, j+1 ), kld )
303 END IF
304 40 CONTINUE
305 END IF
306 RETURN
307*
308 50 CONTINUE
309 info = j
310 RETURN
311*
312* End of SPBSTF
313*
314 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ssyr(uplo, n, alpha, x, incx, a, lda)
SSYR
Definition ssyr.f:132
subroutine spbstf(uplo, n, kd, ab, ldab, info)
SPBSTF
Definition spbstf.f:150
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79