3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download SSYTRF + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssytrf.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssytrf.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssytrf.f">
21 * SUBROUTINE SSYTRF( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, LDA, LWORK, N
27 * .. Array Arguments ..
29 * REAL A( LDA, * ), WORK( * )
38 *> SSYTRF computes the factorization of a real symmetric matrix A using
39 *> the Bunch-Kaufman diagonal pivoting method. The form of the
42 *> A = U*D*U**T or A = L*D*L**T
44 *> where U (or L) is a product of permutation and unit upper (lower)
45 *> triangular matrices, and D is symmetric and block diagonal with
46 *> 1-by-1 and 2-by-2 diagonal blocks.
48 *> This is the blocked version of the algorithm, calling Level 3 BLAS.
56 *> UPLO is CHARACTER*1
57 *> = 'U': Upper triangle of A is stored;
58 *> = 'L': Lower triangle of A is stored.
64 *> The order of the matrix A. N >= 0.
69 *> A is REAL array, dimension (LDA,N)
70 *> On entry, the symmetric matrix A. If UPLO = 'U', the leading
71 *> N-by-N upper triangular part of A contains the upper
72 *> triangular part of the matrix A, and the strictly lower
73 *> triangular part of A is not referenced. If UPLO = 'L', the
74 *> leading N-by-N lower triangular part of A contains the lower
75 *> triangular part of the matrix A, and the strictly upper
76 *> triangular part of A is not referenced.
78 *> On exit, the block diagonal matrix D and the multipliers used
79 *> to obtain the factor U or L (see below for further details).
85 *> The leading dimension of the array A. LDA >= max(1,N).
90 *> IPIV is INTEGER array, dimension (N)
91 *> Details of the interchanges and the block structure of D.
92 *> If IPIV(k) > 0, then rows and columns k and IPIV(k) were
93 *> interchanged and D(k,k) is a 1-by-1 diagonal block.
94 *> If UPLO = 'U' and IPIV(k) = IPIV(k-1) < 0, then rows and
95 *> columns k-1 and -IPIV(k) were interchanged and D(k-1:k,k-1:k)
96 *> is a 2-by-2 diagonal block. If UPLO = 'L' and IPIV(k) =
97 *> IPIV(k+1) < 0, then rows and columns k+1 and -IPIV(k) were
98 *> interchanged and D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
103 *> WORK is REAL array, dimension (MAX(1,LWORK))
104 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
110 *> The length of WORK. LWORK >=1. For best performance
111 *> LWORK >= N*NB, where NB is the block size returned by ILAENV.
113 *> If LWORK = -1, then a workspace query is assumed; the routine
114 *> only calculates the optimal size of the WORK array, returns
115 *> this value as the first entry of the WORK array, and no error
116 *> message related to LWORK is issued by XERBLA.
122 *> = 0: successful exit
123 *> < 0: if INFO = -i, the i-th argument had an illegal value
124 *> > 0: if INFO = i, D(i,i) is exactly zero. The factorization
125 *> has been completed, but the block diagonal matrix D is
126 *> exactly singular, and division by zero will occur if it
127 *> is used to solve a system of equations.
133 *> \author Univ. of Tennessee
134 *> \author Univ. of California Berkeley
135 *> \author Univ. of Colorado Denver
138 *> \date November 2011
140 *> \ingroup realSYcomputational
142 *> \par Further Details:
143 * =====================
147 *> If UPLO = 'U', then A = U*D*U**T, where
148 *> U = P(n)*U(n)* ... *P(k)U(k)* ...,
149 *> i.e., U is a product of terms P(k)*U(k), where k decreases from n to
150 *> 1 in steps of 1 or 2, and D is a block diagonal matrix with 1-by-1
151 *> and 2-by-2 diagonal blocks D(k). P(k) is a permutation matrix as
152 *> defined by IPIV(k), and U(k) is a unit upper triangular matrix, such
153 *> that if the diagonal block D(k) is of order s (s = 1 or 2), then
156 *> U(k) = ( 0 I 0 ) s
160 *> If s = 1, D(k) overwrites A(k,k), and v overwrites A(1:k-1,k).
161 *> If s = 2, the upper triangle of D(k) overwrites A(k-1,k-1), A(k-1,k),
162 *> and A(k,k), and v overwrites A(1:k-2,k-1:k).
164 *> If UPLO = 'L', then A = L*D*L**T, where
165 *> L = P(1)*L(1)* ... *P(k)*L(k)* ...,
166 *> i.e., L is a product of terms P(k)*L(k), where k increases from 1 to
167 *> n in steps of 1 or 2, and D is a block diagonal matrix with 1-by-1
168 *> and 2-by-2 diagonal blocks D(k). P(k) is a permutation matrix as
169 *> defined by IPIV(k), and L(k) is a unit lower triangular matrix, such
170 *> that if the diagonal block D(k) is of order s (s = 1 or 2), then
173 *> L(k) = ( 0 I 0 ) s
177 *> If s = 1, D(k) overwrites A(k,k), and v overwrites A(k+1:n,k).
178 *> If s = 2, the lower triangle of D(k) overwrites A(k,k), A(k+1,k),
179 *> and A(k+1,k+1), and v overwrites A(k+2:n,k:k+1).
182 * =====================================================================
183 SUBROUTINE SSYTRF( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
185 * -- LAPACK computational routine (version 3.4.0) --
186 * -- LAPACK is a software package provided by Univ. of Tennessee, --
187 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
190 * .. Scalar Arguments ..
192 INTEGER INFO, LDA, LWORK, N
194 * .. Array Arguments ..
196 REAL A( LDA, * ), WORK( * )
199 * =====================================================================
201 * .. Local Scalars ..
202 LOGICAL LQUERY, UPPER
203 INTEGER IINFO, IWS, J, K, KB, LDWORK, LWKOPT, NB, NBMIN
205 * .. External Functions ..
208 EXTERNAL LSAME, ILAENV
210 * .. External Subroutines ..
211 EXTERNAL SLASYF, SSYTF2, XERBLA
213 * .. Intrinsic Functions ..
216 * .. Executable Statements ..
218 * Test the input parameters.
221 UPPER = LSAME( UPLO, 'U' )
222 LQUERY = ( LWORK.EQ.-1 )
223 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
225 ELSE IF( N.LT.0 ) THEN
227 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
229 ELSE IF( LWORK.LT.1 .AND. .NOT.LQUERY ) THEN
235 * Determine the block size
237 NB = ILAENV( 1, 'SSYTRF', UPLO, N, -1, -1, -1 )
243 CALL XERBLA( 'SSYTRF', -INFO )
245 ELSE IF( LQUERY ) THEN
251 IF( NB.GT.1 .AND. NB.LT.N ) THEN
253 IF( LWORK.LT.IWS ) THEN
254 NB = MAX( LWORK / LDWORK, 1 )
255 NBMIN = MAX( 2, ILAENV( 2, 'SSYTRF', UPLO, N, -1, -1, -1 ) )
265 * Factorize A as U*D*U**T using the upper triangle of A
267 * K is the main loop index, decreasing from N to 1 in steps of
268 * KB, where KB is the number of columns factorized by SLASYF;
269 * KB is either NB or NB-1, or K for the last block
274 * If K < 1, exit from loop
281 * Factorize columns k-kb+1:k of A and use blocked code to
282 * update columns 1:k-kb
284 CALL SLASYF( UPLO, K, NB, KB, A, LDA, IPIV, WORK, LDWORK,
288 * Use unblocked code to factorize columns 1:k of A
290 CALL SSYTF2( UPLO, K, A, LDA, IPIV, IINFO )
294 * Set INFO on the first occurrence of a zero pivot
296 IF( INFO.EQ.0 .AND. IINFO.GT.0 )
299 * Decrease K and return to the start of the main loop
306 * Factorize A as L*D*L**T using the lower triangle of A
308 * K is the main loop index, increasing from 1 to N in steps of
309 * KB, where KB is the number of columns factorized by SLASYF;
310 * KB is either NB or NB-1, or N-K+1 for the last block
315 * If K > N, exit from loop
322 * Factorize columns k:k+kb-1 of A and use blocked code to
323 * update columns k+kb:n
325 CALL SLASYF( UPLO, N-K+1, NB, KB, A( K, K ), LDA, IPIV( K ),
326 $ WORK, LDWORK, IINFO )
329 * Use unblocked code to factorize columns k:n of A
331 CALL SSYTF2( UPLO, N-K+1, A( K, K ), LDA, IPIV( K ), IINFO )
335 * Set INFO on the first occurrence of a zero pivot
337 IF( INFO.EQ.0 .AND. IINFO.GT.0 )
338 $ INFO = IINFO + K - 1
342 DO 30 J = K, K + KB - 1
343 IF( IPIV( J ).GT.0 ) THEN
344 IPIV( J ) = IPIV( J ) + K - 1
346 IPIV( J ) = IPIV( J ) - K + 1
350 * Increase K and return to the start of the main loop