LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
chesv_rook.f
Go to the documentation of this file.
1 *> \brief \b CHESV_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using the bounded Bunch-Kaufman ("rook") diagonal pivoting method
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 *> \htmlonly
9 *> Download CHESV_ROOK + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/chesv_rook.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/chesv_rook.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/chesv_rook.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CHESV_ROOK( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
22 * LWORK, INFO )
23 *
24 * .. Scalar Arguments ..
25 * CHARACTER UPLO
26 * INTEGER INFO, LDA, LDB, LWORK, N, NRHS
27 * ..
28 * .. Array Arguments ..
29 * INTEGER IPIV( * )
30 * COMPLEX A( LDA, * ), B( LDB, * ), WORK( * )
31 * ..
32 *
33 *
34 *> \par Purpose:
35 * =============
36 *>
37 *> \verbatim
38 *>
39 *> CHESV_ROOK computes the solution to a complex system of linear equations
40 *> A * X = B,
41 *> where A is an N-by-N Hermitian matrix and X and B are N-by-NRHS
42 *> matrices.
43 *>
44 *> The bounded Bunch-Kaufman ("rook") diagonal pivoting method is used
45 *> 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 Hermitian and block diagonal with
50 *> 1-by-1 and 2-by-2 diagonal blocks.
51 *>
52 *> CHETRF_ROOK is called to compute the factorization of a complex
53 *> Hermition matrix A using the bounded Bunch-Kaufman ("rook") diagonal
54 *> pivoting method.
55 *>
56 *> The factored form of A is then used to solve the system
57 *> of equations A * X = B by calling CHETRS_ROOK (uses BLAS 2).
58 *> \endverbatim
59 *
60 * Arguments:
61 * ==========
62 *
63 *> \param[in] UPLO
64 *> \verbatim
65 *> UPLO is CHARACTER*1
66 *> = 'U': Upper triangle of A is stored;
67 *> = 'L': Lower triangle of A is stored.
68 *> \endverbatim
69 *>
70 *> \param[in] N
71 *> \verbatim
72 *> N is INTEGER
73 *> The number of linear equations, i.e., the order of the
74 *> matrix A. N >= 0.
75 *> \endverbatim
76 *>
77 *> \param[in] NRHS
78 *> \verbatim
79 *> NRHS is INTEGER
80 *> The number of right hand sides, i.e., the number of columns
81 *> of the matrix B. NRHS >= 0.
82 *> \endverbatim
83 *>
84 *> \param[in,out] A
85 *> \verbatim
86 *> A is COMPLEX array, dimension (LDA,N)
87 *> On entry, the Hermitian 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.
94 *>
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**H or A = L*D*L**H as computed by
98 *> CHETRF_ROOK.
99 *> \endverbatim
100 *>
101 *> \param[in] LDA
102 *> \verbatim
103 *> LDA is INTEGER
104 *> The leading dimension of the array A. LDA >= max(1,N).
105 *> \endverbatim
106 *>
107 *> \param[out] IPIV
108 *> \verbatim
109 *> IPIV is INTEGER array, dimension (N)
110 *> Details of the interchanges and the block structure of D.
111 *>
112 *> If UPLO = 'U':
113 *> Only the last KB elements of IPIV are set.
114 *>
115 *> If IPIV(k) > 0, then rows and columns k and IPIV(k) were
116 *> interchanged and D(k,k) is a 1-by-1 diagonal block.
117 *>
118 *> If IPIV(k) < 0 and IPIV(k-1) < 0, then rows and
119 *> columns k and -IPIV(k) were interchanged and rows and
120 *> columns k-1 and -IPIV(k-1) were inerchaged,
121 *> D(k-1:k,k-1:k) is a 2-by-2 diagonal block.
122 *>
123 *> If UPLO = 'L':
124 *> Only the first KB elements of IPIV are set.
125 *>
126 *> If IPIV(k) > 0, then rows and columns k and IPIV(k)
127 *> were interchanged and D(k,k) is a 1-by-1 diagonal block.
128 *>
129 *> If IPIV(k) < 0 and IPIV(k+1) < 0, then rows and
130 *> columns k and -IPIV(k) were interchanged and rows and
131 *> columns k+1 and -IPIV(k+1) were inerchaged,
132 *> D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
133 *> \endverbatim
134 *>
135 *> \param[in,out] B
136 *> \verbatim
137 *> B is COMPLEX array, dimension (LDB,NRHS)
138 *> On entry, the N-by-NRHS right hand side matrix B.
139 *> On exit, if INFO = 0, the N-by-NRHS solution matrix X.
140 *> \endverbatim
141 *>
142 *> \param[in] LDB
143 *> \verbatim
144 *> LDB is INTEGER
145 *> The leading dimension of the array B. LDB >= max(1,N).
146 *> \endverbatim
147 *>
148 *> \param[out] WORK
149 *> \verbatim
150 *> WORK is COMPLEX array, dimension (MAX(1,LWORK))
151 *> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
152 *> \endverbatim
153 *>
154 *> \param[in] LWORK
155 *> \verbatim
156 *> LWORK is INTEGER
157 *> The length of WORK. LWORK >= 1, and for best performance
158 *> LWORK >= max(1,N*NB), where NB is the optimal blocksize for
159 *> CHETRF_ROOK.
160 *> for LWORK < N, TRS will be done with Level BLAS 2
161 *> for LWORK >= N, TRS will be done with Level BLAS 3
162 *>
163 *> If LWORK = -1, then a workspace query is assumed; the routine
164 *> only calculates the optimal size of the WORK array, returns
165 *> this value as the first entry of the WORK array, and no error
166 *> message related to LWORK is issued by XERBLA.
167 *> \endverbatim
168 *>
169 *> \param[out] INFO
170 *> \verbatim
171 *> INFO is INTEGER
172 *> = 0: successful exit
173 *> < 0: if INFO = -i, the i-th argument had an illegal value
174 *> > 0: if INFO = i, D(i,i) is exactly zero. The factorization
175 *> has been completed, but the block diagonal matrix D is
176 *> exactly singular, so the solution could not be computed.
177 *> \endverbatim
178 *
179 * Authors:
180 * ========
181 *
182 *> \author Univ. of Tennessee
183 *> \author Univ. of California Berkeley
184 *> \author Univ. of Colorado Denver
185 *> \author NAG Ltd.
186 *
187 *> \date November 2013
188 *
189 *> \ingroup complexHEsolve
190 *>
191 *> \verbatim
192 *>
193 *> November 2013, Igor Kozachenko,
194 *> Computer Science Division,
195 *> University of California, Berkeley
196 *>
197 *> September 2007, Sven Hammarling, Nicholas J. Higham, Craig Lucas,
198 *> School of Mathematics,
199 *> University of Manchester
200 *>
201 *> \endverbatim
202 *
203 *
204 * =====================================================================
205  SUBROUTINE chesv_rook( UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK,
206  $ lwork, info )
207 *
208 * -- LAPACK driver routine (version 3.5.0) --
209 * -- LAPACK is a software package provided by Univ. of Tennessee, --
210 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
211 * November 2013
212 *
213 * .. Scalar Arguments ..
214  CHARACTER UPLO
215  INTEGER INFO, LDA, LDB, LWORK, N, NRHS
216 * ..
217 * .. Array Arguments ..
218  INTEGER IPIV( * )
219  COMPLEX A( lda, * ), B( ldb, * ), WORK( * )
220 * ..
221 *
222 * =====================================================================
223 *
224 * .. Local Scalars ..
225  LOGICAL LQUERY
226  INTEGER LWKOPT, NB
227 * ..
228 * .. External Functions ..
229  LOGICAL LSAME
230  INTEGER ILAENV
231  EXTERNAL lsame, ilaenv
232 * ..
233 * .. External Subroutines ..
234  EXTERNAL xerbla, chetrf_rook, chetrs_rook
235 * ..
236 * .. Intrinsic Functions ..
237  INTRINSIC max
238 * ..
239 * .. Executable Statements ..
240 *
241 * Test the input parameters.
242 *
243  info = 0
244  lquery = ( lwork.EQ.-1 )
245  IF( .NOT.lsame( uplo, 'U' ) .AND. .NOT.lsame( uplo, 'L' ) ) THEN
246  info = -1
247  ELSE IF( n.LT.0 ) THEN
248  info = -2
249  ELSE IF( nrhs.LT.0 ) THEN
250  info = -3
251  ELSE IF( lda.LT.max( 1, n ) ) THEN
252  info = -5
253  ELSE IF( ldb.LT.max( 1, n ) ) THEN
254  info = -8
255  ELSE IF( lwork.LT.1 .AND. .NOT.lquery ) THEN
256  info = -10
257  END IF
258 *
259  IF( info.EQ.0 ) THEN
260  IF( n.EQ.0 ) THEN
261  lwkopt = 1
262  ELSE
263  nb = ilaenv( 1, 'CHETRF_ROOK', uplo, n, -1, -1, -1 )
264  lwkopt = n*nb
265  END IF
266  work( 1 ) = lwkopt
267  END IF
268 *
269  IF( info.NE.0 ) THEN
270  CALL xerbla( 'CHESV_ROOK ', -info )
271  RETURN
272  ELSE IF( lquery ) THEN
273  RETURN
274  END IF
275 *
276 * Compute the factorization A = U*D*U**H or A = L*D*L**H.
277 *
278  CALL chetrf_rook( uplo, n, a, lda, ipiv, work, lwork, info )
279  IF( info.EQ.0 ) THEN
280 *
281 * Solve the system A*X = B, overwriting B with X.
282 *
283 * Solve with TRS ( Use Level BLAS 2)
284 *
285  CALL chetrs_rook( uplo, n, nrhs, a, lda, ipiv, b, ldb, info )
286 *
287  END IF
288 *
289  work( 1 ) = lwkopt
290 *
291  RETURN
292 *
293 * End of CHESV_ROOK
294 *
295  END
subroutine chetrs_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CHETRS_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using fac...
Definition: chetrs_rook.f:138
subroutine chetrf_rook(UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO)
CHETRF_ROOK computes the factorization of a complex Hermitian indefinite matrix using the bounded Bun...
Definition: chetrf_rook.f:214
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine chesv_rook(UPLO, N, NRHS, A, LDA, IPIV, B, LDB, WORK, LWORK, INFO)
CHESV_ROOK computes the solution to a system of linear equations A * X = B for HE matrices using the ...
Definition: chesv_rook.f:207