1 *> \brief \b CHETRI_ROOK computes the inverse of HE matrix using the factorization obtained with the bounded Bunch-Kaufman ("rook") diagonal pivoting method.
3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CHETRI_ROOK + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/chetri_rook.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/chetri_rook.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/chetri_rook.f">
21 * SUBROUTINE CHETRI_ROOK( UPLO, N, A, LDA, IPIV, WORK, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, LDA, N
27 * .. Array Arguments ..
29 * COMPLEX A( LDA, * ), WORK( * )
38 *> CHETRI_ROOK computes the inverse of a complex Hermitian indefinite matrix
39 *> A using the factorization A = U*D*U**H or A = L*D*L**H computed by
48 *> UPLO is CHARACTER*1
49 *> Specifies whether the details of the factorization are stored
50 *> as an upper or lower triangular matrix.
51 *> = 'U': Upper triangular, form is A = U*D*U**H;
52 *> = 'L': Lower triangular, form is A = L*D*L**H.
58 *> The order of the matrix A. N >= 0.
63 *> A is COMPLEX array, dimension (LDA,N)
64 *> On entry, the block diagonal matrix D and the multipliers
65 *> used to obtain the factor U or L as computed by CHETRF_ROOK.
67 *> On exit, if INFO = 0, the (Hermitian) inverse of the original
68 *> matrix. If UPLO = 'U', the upper triangular part of the
69 *> inverse is formed and the part of A below the diagonal is not
70 *> referenced; if UPLO = 'L' the lower triangular part of the
71 *> inverse is formed and the part of A above the diagonal is
78 *> The leading dimension of the array A. LDA >= max(1,N).
83 *> IPIV is INTEGER array, dimension (N)
84 *> Details of the interchanges and the block structure of D
85 *> as determined by CHETRF_ROOK.
90 *> WORK is COMPLEX array, dimension (N)
96 *> = 0: successful exit
97 *> < 0: if INFO = -i, the i-th argument had an illegal value
98 *> > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
99 *> inverse could not be computed.
105 *> \author Univ. of Tennessee
106 *> \author Univ. of California Berkeley
107 *> \author Univ. of Colorado Denver
110 *> \date November 2013
112 *> \ingroup complexHEcomputational
114 *> \par Contributors:
119 *> November 2013, Igor Kozachenko,
120 *> Computer Science Division,
121 *> University of California, Berkeley
123 *> September 2007, Sven Hammarling, Nicholas J. Higham, Craig Lucas,
124 *> School of Mathematics,
125 *> University of Manchester
128 * =====================================================================
129 SUBROUTINE CHETRI_ROOK( UPLO, N, A, LDA, IPIV, WORK, INFO )
131 * -- LAPACK computational routine (version 3.5.0) --
132 * -- LAPACK is a software package provided by Univ. of Tennessee, --
133 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
136 * .. Scalar Arguments ..
140 * .. Array Arguments ..
142 COMPLEX A( LDA, * ), WORK( * )
145 * =====================================================================
150 PARAMETER ( ONE = 1.0E+0, CONE = ( 1.0E+0, 0.0E+0 ),
151 $ CZERO = ( 0.0E+0, 0.0E+0 ) )
153 * .. Local Scalars ..
155 INTEGER J, K, KP, KSTEP
159 * .. External Functions ..
162 EXTERNAL LSAME, CDOTC
164 * .. External Subroutines ..
165 EXTERNAL CCOPY, CHEMV, CSWAP, XERBLA
167 * .. Intrinsic Functions ..
168 INTRINSIC ABS, CONJG, MAX, REAL
170 * .. Executable Statements ..
172 * Test the input parameters.
175 UPPER = LSAME( UPLO, 'U' )
176 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
178 ELSE IF( N.LT.0 ) THEN
180 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
184 CALL XERBLA( 'CHETRI_ROOK', -INFO )
188 * Quick return if possible
193 * Check that the diagonal matrix D is nonsingular.
197 * Upper triangular storage: examine D from bottom to top
199 DO 10 INFO = N, 1, -1
200 IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.CZERO )
205 * Lower triangular storage: examine D from top to bottom.
208 IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.CZERO )
216 * Compute inv(A) from the factorization A = U*D*U**H.
218 * K is the main loop index, increasing from 1 to N in steps of
219 * 1 or 2, depending on the size of the diagonal blocks.
224 * If K > N, exit from loop.
229 IF( IPIV( K ).GT.0 ) THEN
231 * 1 x 1 diagonal block
233 * Invert the diagonal block.
235 A( K, K ) = ONE / REAL( A( K, K ) )
237 * Compute column K of the inverse.
240 CALL CCOPY( K-1, A( 1, K ), 1, WORK, 1 )
241 CALL CHEMV( UPLO, K-1, -CONE, A, LDA, WORK, 1, CZERO,
243 A( K, K ) = A( K, K ) - REAL( CDOTC( K-1, WORK, 1, A( 1,
249 * 2 x 2 diagonal block
251 * Invert the diagonal block.
253 T = ABS( A( K, K+1 ) )
254 AK = REAL( A( K, K ) ) / T
255 AKP1 = REAL( A( K+1, K+1 ) ) / T
256 AKKP1 = A( K, K+1 ) / T
257 D = T*( AK*AKP1-ONE )
259 A( K+1, K+1 ) = AK / D
260 A( K, K+1 ) = -AKKP1 / D
262 * Compute columns K and K+1 of the inverse.
265 CALL CCOPY( K-1, A( 1, K ), 1, WORK, 1 )
266 CALL CHEMV( UPLO, K-1, -CONE, A, LDA, WORK, 1, CZERO,
268 A( K, K ) = A( K, K ) - REAL( CDOTC( K-1, WORK, 1, A( 1,
270 A( K, K+1 ) = A( K, K+1 ) -
271 $ CDOTC( K-1, A( 1, K ), 1, A( 1, K+1 ), 1 )
272 CALL CCOPY( K-1, A( 1, K+1 ), 1, WORK, 1 )
273 CALL CHEMV( UPLO, K-1, -CONE, A, LDA, WORK, 1, CZERO,
275 A( K+1, K+1 ) = A( K+1, K+1 ) -
276 $ REAL( CDOTC( K-1, WORK, 1, A( 1, K+1 ),
282 IF( KSTEP.EQ.1 ) THEN
284 * Interchange rows and columns K and IPIV(K) in the leading
285 * submatrix A(1:k,1:k)
291 $ CALL CSWAP( KP-1, A( 1, K ), 1, A( 1, KP ), 1 )
293 DO 40 J = KP + 1, K - 1
294 TEMP = CONJG( A( J, K ) )
295 A( J, K ) = CONJG( A( KP, J ) )
299 A( KP, K ) = CONJG( A( KP, K ) )
302 A( K, K ) = A( KP, KP )
307 * Interchange rows and columns K and K+1 with -IPIV(K) and
308 * -IPIV(K+1) in the leading submatrix A(k+1:n,k+1:n)
310 * (1) Interchange rows and columns K and -IPIV(K)
316 $ CALL CSWAP( KP-1, A( 1, K ), 1, A( 1, KP ), 1 )
318 DO 50 J = KP + 1, K - 1
319 TEMP = CONJG( A( J, K ) )
320 A( J, K ) = CONJG( A( KP, J ) )
324 A( KP, K ) = CONJG( A( KP, K ) )
327 A( K, K ) = A( KP, KP )
331 A( K, K+1 ) = A( KP, K+1 )
335 * (2) Interchange rows and columns K+1 and -IPIV(K+1)
342 $ CALL CSWAP( KP-1, A( 1, K ), 1, A( 1, KP ), 1 )
344 DO 60 J = KP + 1, K - 1
345 TEMP = CONJG( A( J, K ) )
346 A( J, K ) = CONJG( A( KP, J ) )
350 A( KP, K ) = CONJG( A( KP, K ) )
353 A( K, K ) = A( KP, KP )
364 * Compute inv(A) from the factorization A = L*D*L**H.
366 * K is the main loop index, decreasing from N to 1 in steps of
367 * 1 or 2, depending on the size of the diagonal blocks.
372 * If K < 1, exit from loop.
377 IF( IPIV( K ).GT.0 ) THEN
379 * 1 x 1 diagonal block
381 * Invert the diagonal block.
383 A( K, K ) = ONE / REAL( A( K, K ) )
385 * Compute column K of the inverse.
388 CALL CCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
389 CALL CHEMV( UPLO, N-K, -CONE, A( K+1, K+1 ), LDA, WORK,
390 $ 1, CZERO, A( K+1, K ), 1 )
391 A( K, K ) = A( K, K ) - REAL( CDOTC( N-K, WORK, 1,
397 * 2 x 2 diagonal block
399 * Invert the diagonal block.
401 T = ABS( A( K, K-1 ) )
402 AK = REAL( A( K-1, K-1 ) ) / T
403 AKP1 = REAL( A( K, K ) ) / T
404 AKKP1 = A( K, K-1 ) / T
405 D = T*( AK*AKP1-ONE )
406 A( K-1, K-1 ) = AKP1 / D
408 A( K, K-1 ) = -AKKP1 / D
410 * Compute columns K-1 and K of the inverse.
413 CALL CCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
414 CALL CHEMV( UPLO, N-K, -CONE, A( K+1, K+1 ), LDA, WORK,
415 $ 1, CZERO, A( K+1, K ), 1 )
416 A( K, K ) = A( K, K ) - REAL( CDOTC( N-K, WORK, 1,
418 A( K, K-1 ) = A( K, K-1 ) -
419 $ CDOTC( N-K, A( K+1, K ), 1, A( K+1, K-1 ),
421 CALL CCOPY( N-K, A( K+1, K-1 ), 1, WORK, 1 )
422 CALL CHEMV( UPLO, N-K, -CONE, A( K+1, K+1 ), LDA, WORK,
423 $ 1, CZERO, A( K+1, K-1 ), 1 )
424 A( K-1, K-1 ) = A( K-1, K-1 ) -
425 $ REAL( CDOTC( N-K, WORK, 1, A( K+1, K-1 ),
431 IF( KSTEP.EQ.1 ) THEN
433 * Interchange rows and columns K and IPIV(K) in the trailing
434 * submatrix A(k:n,k:n)
440 $ CALL CSWAP( N-KP, A( KP+1, K ), 1, A( KP+1, KP ), 1 )
442 DO 90 J = K + 1, KP - 1
443 TEMP = CONJG( A( J, K ) )
444 A( J, K ) = CONJG( A( KP, J ) )
448 A( KP, K ) = CONJG( A( KP, K ) )
451 A( K, K ) = A( KP, KP )
456 * Interchange rows and columns K and K-1 with -IPIV(K) and
457 * -IPIV(K-1) in the trailing submatrix A(k-1:n,k-1:n)
459 * (1) Interchange rows and columns K and -IPIV(K)
465 $ CALL CSWAP( N-KP, A( KP+1, K ), 1, A( KP+1, KP ), 1 )
467 DO 100 J = K + 1, KP - 1
468 TEMP = CONJG( A( J, K ) )
469 A( J, K ) = CONJG( A( KP, J ) )
473 A( KP, K ) = CONJG( A( KP, K ) )
476 A( K, K ) = A( KP, KP )
480 A( K, K-1 ) = A( KP, K-1 )
484 * (2) Interchange rows and columns K-1 and -IPIV(K-1)
491 $ CALL CSWAP( N-KP, A( KP+1, K ), 1, A( KP+1, KP ), 1 )
493 DO 110 J = K + 1, KP - 1
494 TEMP = CONJG( A( J, K ) )
495 A( J, K ) = CONJG( A( KP, J ) )
499 A( KP, K ) = CONJG( A( KP, K ) )
502 A( K, K ) = A( KP, KP )