1 SUBROUTINE DSYTRF
( UPLO
, N
, A
, LDA
, IPIV
, WORK
, LWORK
, INFO
)
3 * -- LAPACK routine
(version
3.1) --
4 * Univ
. of Tennessee
, Univ
. of California Berkeley and NAG Ltd
..
7 * .. Scalar Arguments
..
9 INTEGER INFO
, LDA
, LWORK
, N
11 * .. Array Arguments
..
13 DOUBLE PRECISION A
( LDA
, * ), WORK
( * )
19 * DSYTRF computes the factorization of a
real symmetric matrix A using
20 * the Bunch
-Kaufman diagonal pivoting method
. The form of the
23 * A
= U*D*U**T or A
= L*D*L**T
25 * where U
(or L
) is a product of permutation and unit upper
(lower
)
26 * triangular matrices
, and D is symmetric and block diagonal with
27 * 1-by
-1 and
2-by
-2 diagonal blocks
.
29 * This is the blocked version of the algorithm
, calling Level
3 BLAS
.
34 * UPLO
(input
) CHARACTER*1
35 * = 'U': Upper triangle of A is stored
;
36 * = 'L': Lower triangle of A is stored
.
39 * The order of the matrix A
. N
>= 0.
41 * A
(input
/output
) DOUBLE PRECISION array
, dimension (LDA
,N
)
42 * On entry
, the symmetric matrix A
. If UPLO
= 'U', the leading
43 * N
-by
-N upper triangular part of A contains the upper
44 * triangular part of the matrix A
, and the strictly lower
45 * triangular part of A is not referenced
. If UPLO
= 'L', the
46 * leading N
-by
-N lower triangular part of A contains the lower
47 * triangular part of the matrix A
, and the strictly upper
48 * triangular part of A is not referenced
.
50 * On exit
, the block diagonal matrix D and the multipliers used
51 * to obtain the factor U or L
(see below
for further details
).
54 * The leading
dimension of the array A
. LDA
>= max
(1,N
).
56 * IPIV
(output
) INTEGER array
, dimension (N
)
57 * Details of the interchanges and the block structure of D
.
58 * If IPIV
(k
) > 0, then rows and columns k and IPIV
(k
) were
59 * interchanged and D
(k
,k
) is a
1-by
-1 diagonal block
.
60 * If UPLO
= 'U' and IPIV
(k
) = IPIV
(k
-1) < 0, then rows and
61 * columns k
-1 and
-IPIV
(k
) were interchanged and D
(k
-1:k
,k
-1:k
)
62 * is a
2-by
-2 diagonal block
. If UPLO
= 'L' and IPIV
(k
) =
63 * IPIV
(k
+1) < 0, then rows and columns k
+1 and
-IPIV
(k
) were
64 * interchanged and D
(k
:k
+1,k
:k
+1) is a
2-by
-2 diagonal block
.
66 * WORK
(workspace
/output
) DOUBLE PRECISION array
, dimension (MAX
(1,LWORK
))
67 * On exit
, if INFO
= 0, WORK
(1) returns the optimal LWORK
.
69 * LWORK
(input
) INTEGER
70 * The length of WORK
. LWORK
>=1. For best performance
71 * LWORK
>= N*NB
, where NB is the block size returned by ILAENV
.
73 * If LWORK
= -1, then a workspace query is assumed
; the routine
74 * only calculates the optimal size of the WORK array
, returns
75 * this value as the first entry of the WORK array
, and no error
76 * message related
to LWORK is issued by XERBLA
.
78 * INFO
(output
) INTEGER
79 * = 0: successful exit
80 * < 0: if INFO
= -i
, the i
-th argument had an illegal value
81 * > 0: if INFO
= i
, D
(i
,i
) is exactly zero
. The factorization
82 * has been completed
, but the block diagonal matrix D is
83 * exactly singular
, and division by zero will occur
if it
84 * is used
to solve a system of equations
.
89 * If UPLO
= 'U', then A
= U*D*U
', where
90 * U = P(n)*U(n)* ... *P(k)U(k)* ...,
91 * i.e., U is a product of terms P(k)*U(k), where k decreases from n to
92 * 1 in steps of 1 or 2, and D is a block diagonal matrix with 1-by-1
93 * and 2-by-2 diagonal blocks D(k). P(k) is a permutation matrix as
94 * defined by IPIV(k), and U(k) is a unit upper triangular matrix, such
95 * that if the diagonal block D(k) is of order s (s = 1 or 2), then
102 * If s = 1, D(k) overwrites A(k,k), and v overwrites A(1:k-1,k).
103 * If s = 2, the upper triangle of D(k) overwrites A(k-1,k-1), A(k-1,k),
104 * and A(k,k), and v overwrites A(1:k-2,k-1:k).
106 * If UPLO = 'L
', then A = L*D*L', where
107 * L
= P
(1)*L
(1)* ... *P
(k
)*L
(k
)* ...,
108 * i
.e
., L is a product of terms P
(k
)*L
(k
), where k increases from
1 to
109 * n in steps of
1 or
2, and D is a block diagonal matrix with
1-by
-1
110 * and
2-by
-2 diagonal blocks D
(k
). P
(k
) is a permutation matrix as
111 * defined by IPIV
(k
), and L
(k
) is a unit lower triangular matrix
, such
112 * that
if the diagonal block D
(k
) is of order s
(s
= 1 or
2), then
119 * If s
= 1, D
(k
) overwrites A
(k
,k
), and v overwrites A
(k
+1:n
,k
).
120 * If s
= 2, the lower triangle of D
(k
) overwrites A
(k
,k
), A
(k
+1,k
),
121 * and A
(k
+1,k
+1), and v overwrites A
(k
+2:n
,k
:k
+1).
123 * =====================================================================
125 * .. Local Scalars
..
126 LOGICAL LQUERY
, UPPER
127 INTEGER IINFO
, IWS
, J
, K
, KB
, LDWORK
, LWKOPT
, NB
, NBMIN
129 * .. External Functions
..
132 EXTERNAL LSAME
, ILAENV
134 * .. External Subroutines
..
135 EXTERNAL DLASYF
, DSYTF2
, XERBLA
137 * .. Intrinsic Functions
..
140 * .. Executable Statements
..
142 * Test the input parameters
.
145 UPPER
= LSAME
( UPLO
, 'U' )
146 LQUERY
= ( LWORK
.EQ
.-1 )
147 IF( .NOT
.UPPER
.AND
. .NOT
.LSAME
( UPLO
, 'L' ) ) THEN
149 ELSE IF( N
.LT
.0 ) THEN
151 ELSE IF( LDA
.LT
.MAX
( 1, N
) ) THEN
153 ELSE IF( LWORK
.LT
.1 .AND
. .NOT
.LQUERY
) THEN
159 * Determine the block size
161 NB
= ILAENV
( 1, 'DSYTRF', UPLO
, N
, -1, -1, -1 )
167 CALL XERBLA
( 'DSYTRF', -INFO
)
169 ELSE IF( LQUERY
) THEN
175 IF( NB
.GT
.1 .AND
. NB
.LT
.N
) THEN
177 IF( LWORK
.LT
.IWS
) THEN
178 NB
= MAX
( LWORK
/ LDWORK
, 1 )
179 NBMIN
= MAX
( 2, ILAENV
( 2, 'DSYTRF', UPLO
, N
, -1, -1, -1 ) )
189 * Factorize A as U*D*U
' using the upper triangle of A
191 * K is the main loop index, decreasing from N to 1 in steps of
192 * KB, where KB is the number of columns factorized by DLASYF;
193 * KB is either NB or NB-1, or K for the last block
198 * If K < 1, exit from loop
205 * Factorize columns k-kb+1:k of A and use blocked code to
206 * update columns 1:k-kb
208 CALL DLASYF( UPLO, K, NB, KB, A, LDA, IPIV, WORK, LDWORK,
212 * Use unblocked code to factorize columns 1:k of A
214 CALL DSYTF2( UPLO, K, A, LDA, IPIV, IINFO )
218 * Set INFO on the first occurrence of a zero pivot
220 IF( INFO.EQ.0 .AND. IINFO.GT.0 )
223 * Decrease K and return to the start of the main loop
230 * Factorize A as L*D*L' using the lower triangle of A
232 * K is the main loop index
, increasing from
1 to N in steps of
233 * KB
, where KB is the number of columns factorized by DLASYF
;
234 * KB is either NB or NB
-1, or N
-K
+1 for the last block
239 * If K
> N
, exit from loop
246 * Factorize columns k
:k
+kb
-1 of A and use blocked code
to
247 * update columns k
+kb
:n
249 CALL DLASYF
( UPLO
, N
-K
+1, NB
, KB
, A
( K
, K
), LDA
, IPIV
( K
),
250 $ WORK
, LDWORK
, IINFO
)
253 * Use unblocked code
to factorize columns k
:n of A
255 CALL DSYTF2
( UPLO
, N
-K
+1, A
( K
, K
), LDA
, IPIV
( K
), IINFO
)
259 * Set INFO on the first occurrence of a zero pivot
261 IF( INFO
.EQ
.0 .AND
. IINFO
.GT
.0 )
262 $ INFO
= IINFO
+ K
- 1
266 DO 30 J
= K
, K
+ KB
- 1
267 IF( IPIV
( J
).GT
.0 ) THEN
268 IPIV
( J
) = IPIV
( J
) + K
- 1
270 IPIV
( J
) = IPIV
( J
) - K
+ 1
274 * Increase K and
return to the start of the main loop