1 *> \brief <b> DSYSV_ROOK computes the solution to system of linear equations A * X = B for SY matrices</b>
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download DSYSV_ROOK + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsysv_rook.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsysv_rook.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsysv_rook.f">
21 * SUBROUTINE DSYSV_ROOK( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
24 * .. Scalar Arguments ..
26 * INTEGER INFO, LDA, LDB, LWORK, N, NRHS
28 * .. Array Arguments ..
30 * DOUBLE PRECISION A( LDA, * ), B( LDB, * ), WORK( * )
39 *> DSYSV_ROOK computes the solution to a real system of linear
42 *> where A is an N-by-N symmetric matrix and X and B are N-by-NRHS
45 *> The diagonal pivoting method is used to factor A as
46 *> A = U * D * U**T, if UPLO = 'U', or
47 *> A = L * D * L**T, if UPLO = 'L',
48 *> where U (or L) is a product of permutation and unit upper (lower)
49 *> triangular matrices, and D is symmetric and block diagonal with
50 *> 1-by-1 and 2-by-2 diagonal blocks.
52 *> DSYTRF_ROOK is called to compute the factorization of a real
53 *> symmetric matrix A using the bounded Bunch-Kaufman ("rook") diagonal
56 *> The factored form of A is then used to solve the system
57 *> of equations A * X = B by calling DSYTRS_ROOK.
65 *> UPLO is CHARACTER*1
66 *> = 'U': Upper triangle of A is stored;
67 *> = 'L': Lower triangle of A is stored.
73 *> The number of linear equations, i.e., the order of the
80 *> The number of right hand sides, i.e., the number of columns
81 *> of the matrix B. NRHS >= 0.
86 *> A is DOUBLE PRECISION array, dimension (LDA,N)
87 *> On entry, the symmetric matrix A. If UPLO = 'U', the leading
88 *> N-by-N upper triangular part of A contains the upper
89 *> triangular part of the matrix A, and the strictly lower
90 *> triangular part of A is not referenced. If UPLO = 'L', the
91 *> leading N-by-N lower triangular part of A contains the lower
92 *> triangular part of the matrix A, and the strictly upper
93 *> triangular part of A is not referenced.
95 *> On exit, if INFO = 0, the block diagonal matrix D and the
96 *> multipliers used to obtain the factor U or L from the
97 *> factorization A = U*D*U**T or A = L*D*L**T as computed by
104 *> The leading dimension of the array A. LDA >= max(1,N).
109 *> IPIV is INTEGER array, dimension (N)
110 *> Details of the interchanges and the block structure of D,
111 *> as determined by DSYTRF_ROOK.
114 *> If IPIV(k) > 0, then rows and columns k and IPIV(k)
115 *> were interchanged and D(k,k) is a 1-by-1 diagonal block.
117 *> If IPIV(k) < 0 and IPIV(k-1) < 0, then rows and
118 *> columns k and -IPIV(k) were interchanged and rows and
119 *> columns k-1 and -IPIV(k-1) were inerchaged,
120 *> D(k-1:k,k-1:k) is a 2-by-2 diagonal block.
123 *> If IPIV(k) > 0, then rows and columns k and IPIV(k)
124 *> were interchanged and D(k,k) is a 1-by-1 diagonal block.
126 *> If IPIV(k) < 0 and IPIV(k+1) < 0, then rows and
127 *> columns k and -IPIV(k) were interchanged and rows and
128 *> columns k+1 and -IPIV(k+1) were inerchaged,
129 *> D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
134 *> B is DOUBLE PRECISION array, dimension (LDB,NRHS)
135 *> On entry, the N-by-NRHS right hand side matrix B.
136 *> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
142 *> The leading dimension of the array B. LDB >= max(1,N).
147 *> WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK))
148 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
154 *> The length of WORK. LWORK >= 1, and for best performance
155 *> LWORK >= max(1,N*NB), where NB is the optimal blocksize for
158 *> TRS will be done with Level 2 BLAS
160 *> If LWORK = -1, then a workspace query is assumed; the routine
161 *> only calculates the optimal size of the WORK array, returns
162 *> this value as the first entry of the WORK array, and no error
163 *> message related to LWORK is issued by XERBLA.
169 *> = 0: successful exit
170 *> < 0: if INFO = -i, the i-th argument had an illegal value
171 *> > 0: if INFO = i, D(i,i) is exactly zero. The factorization
172 *> has been completed, but the block diagonal matrix D is
173 *> exactly singular, so the solution could not be computed.
179 *> \author Univ. of Tennessee
180 *> \author Univ. of California Berkeley
181 *> \author Univ. of Colorado Denver
186 *> \ingroup doubleSYsolve
188 *> \par Contributors:
193 *> April 2012, Igor Kozachenko,
194 *> Computer Science Division,
195 *> University of California, Berkeley
197 *> September 2007, Sven Hammarling, Nicholas J. Higham, Craig Lucas,
198 *> School of Mathematics,
199 *> University of Manchester
203 * =====================================================================
204 SUBROUTINE DSYSV_ROOK( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
207 * -- LAPACK driver routine (version 3.4.1) --
208 * -- LAPACK is a software package provided by Univ. of Tennessee, --
209 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
212 * .. Scalar Arguments ..
214 INTEGER INFO, LDA, LDB, LWORK, N, NRHS
216 * .. Array Arguments ..
218 DOUBLE PRECISION A( LDA, * ), B( LDB, * ), WORK( * )
221 * =====================================================================
223 * .. Local Scalars ..
227 * .. External Functions ..
231 * .. External Subroutines ..
232 EXTERNAL XERBLA, DSYTRF_ROOK, DSYTRS_ROOK
234 * .. Intrinsic Functions ..
237 * .. Executable Statements ..
239 * Test the input parameters.
242 LQUERY = ( LWORK.EQ.-1 )
243 IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
245 ELSE IF( N.LT.0 ) THEN
247 ELSE IF( NRHS.LT.0 ) THEN
249 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
251 ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
253 ELSE IF( LWORK.LT.1 .AND. .NOT.LQUERY ) THEN
261 CALL DSYTRF_ROOK( UPLO, N, A, LDA, IPIV, WORK, -1, INFO )
268 CALL XERBLA( 'DSYSV_ROOK ', -INFO )
270 ELSE IF( LQUERY ) THEN
274 * Compute the factorization A = U*D*U**T or A = L*D*L**T.
276 CALL DSYTRF_ROOK( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
279 * Solve the system A*X = B, overwriting B with X.
281 * Solve with TRS_ROOK ( Use Level 2 BLAS)
283 CALL DSYTRS_ROOK( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO )