3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download CHETRI + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/chetri.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/chetri.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/chetri.f">
21 * SUBROUTINE CHETRI( 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 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.
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.
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 2011
112 *> \ingroup complexHEcomputational
114 * =====================================================================
115 SUBROUTINE CHETRI( UPLO, N, A, LDA, IPIV, WORK, INFO )
117 * -- LAPACK computational routine (version 3.4.0) --
118 * -- LAPACK is a software package provided by Univ. of Tennessee, --
119 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
122 * .. Scalar Arguments ..
126 * .. Array Arguments ..
128 COMPLEX A( LDA, * ), WORK( * )
131 * =====================================================================
136 PARAMETER ( ONE = 1.0E+0, CONE = ( 1.0E+0, 0.0E+0 ),
137 $ ZERO = ( 0.0E+0, 0.0E+0 ) )
139 * .. Local Scalars ..
141 INTEGER J, K, KP, KSTEP
145 * .. External Functions ..
148 EXTERNAL LSAME, CDOTC
150 * .. External Subroutines ..
151 EXTERNAL CCOPY, CHEMV, CSWAP, XERBLA
153 * .. Intrinsic Functions ..
154 INTRINSIC ABS, CONJG, MAX, REAL
156 * .. Executable Statements ..
158 * Test the input parameters.
161 UPPER = LSAME( UPLO, 'U' )
162 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
164 ELSE IF( N.LT.0 ) THEN
166 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
170 CALL XERBLA( 'CHETRI', -INFO )
174 * Quick return if possible
179 * Check that the diagonal matrix D is nonsingular.
183 * Upper triangular storage: examine D from bottom to top
185 DO 10 INFO = N, 1, -1
186 IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.ZERO )
191 * Lower triangular storage: examine D from top to bottom.
194 IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.ZERO )
202 * Compute inv(A) from the factorization A = U*D*U**H.
204 * K is the main loop index, increasing from 1 to N in steps of
205 * 1 or 2, depending on the size of the diagonal blocks.
210 * If K > N, exit from loop.
215 IF( IPIV( K ).GT.0 ) THEN
217 * 1 x 1 diagonal block
219 * Invert the diagonal block.
221 A( K, K ) = ONE / REAL( A( K, K ) )
223 * Compute column K of the inverse.
226 CALL CCOPY( K-1, A( 1, K ), 1, WORK, 1 )
227 CALL CHEMV( UPLO, K-1, -CONE, A, LDA, WORK, 1, ZERO,
229 A( K, K ) = A( K, K ) - REAL( CDOTC( K-1, WORK, 1, A( 1,
235 * 2 x 2 diagonal block
237 * Invert the diagonal block.
239 T = ABS( A( K, K+1 ) )
240 AK = REAL( A( K, K ) ) / T
241 AKP1 = REAL( A( K+1, K+1 ) ) / T
242 AKKP1 = A( K, K+1 ) / T
243 D = T*( AK*AKP1-ONE )
245 A( K+1, K+1 ) = AK / D
246 A( K, K+1 ) = -AKKP1 / D
248 * Compute columns K and K+1 of the inverse.
251 CALL CCOPY( K-1, A( 1, K ), 1, WORK, 1 )
252 CALL CHEMV( UPLO, K-1, -CONE, A, LDA, WORK, 1, ZERO,
254 A( K, K ) = A( K, K ) - REAL( CDOTC( K-1, WORK, 1, A( 1,
256 A( K, K+1 ) = A( K, K+1 ) -
257 $ CDOTC( K-1, A( 1, K ), 1, A( 1, K+1 ), 1 )
258 CALL CCOPY( K-1, A( 1, K+1 ), 1, WORK, 1 )
259 CALL CHEMV( UPLO, K-1, -CONE, A, LDA, WORK, 1, ZERO,
261 A( K+1, K+1 ) = A( K+1, K+1 ) -
262 $ REAL( CDOTC( K-1, WORK, 1, A( 1, K+1 ),
268 KP = ABS( IPIV( K ) )
271 * Interchange rows and columns K and KP in the leading
272 * submatrix A(1:k+1,1:k+1)
274 CALL CSWAP( KP-1, A( 1, K ), 1, A( 1, KP ), 1 )
275 DO 40 J = KP + 1, K - 1
276 TEMP = CONJG( A( J, K ) )
277 A( J, K ) = CONJG( A( KP, J ) )
280 A( KP, K ) = CONJG( A( KP, K ) )
282 A( K, K ) = A( KP, KP )
284 IF( KSTEP.EQ.2 ) THEN
286 A( K, K+1 ) = A( KP, K+1 )
297 * Compute inv(A) from the factorization A = L*D*L**H.
299 * K is the main loop index, increasing from 1 to N in steps of
300 * 1 or 2, depending on the size of the diagonal blocks.
305 * If K < 1, exit from loop.
310 IF( IPIV( K ).GT.0 ) THEN
312 * 1 x 1 diagonal block
314 * Invert the diagonal block.
316 A( K, K ) = ONE / REAL( A( K, K ) )
318 * Compute column K of the inverse.
321 CALL CCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
322 CALL CHEMV( UPLO, N-K, -CONE, A( K+1, K+1 ), LDA, WORK,
323 $ 1, ZERO, A( K+1, K ), 1 )
324 A( K, K ) = A( K, K ) - REAL( CDOTC( N-K, WORK, 1,
330 * 2 x 2 diagonal block
332 * Invert the diagonal block.
334 T = ABS( A( K, K-1 ) )
335 AK = REAL( A( K-1, K-1 ) ) / T
336 AKP1 = REAL( A( K, K ) ) / T
337 AKKP1 = A( K, K-1 ) / T
338 D = T*( AK*AKP1-ONE )
339 A( K-1, K-1 ) = AKP1 / D
341 A( K, K-1 ) = -AKKP1 / D
343 * Compute columns K-1 and K of the inverse.
346 CALL CCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
347 CALL CHEMV( UPLO, N-K, -CONE, A( K+1, K+1 ), LDA, WORK,
348 $ 1, ZERO, A( K+1, K ), 1 )
349 A( K, K ) = A( K, K ) - REAL( CDOTC( N-K, WORK, 1,
351 A( K, K-1 ) = A( K, K-1 ) -
352 $ CDOTC( N-K, A( K+1, K ), 1, A( K+1, K-1 ),
354 CALL CCOPY( N-K, A( K+1, K-1 ), 1, WORK, 1 )
355 CALL CHEMV( UPLO, N-K, -CONE, A( K+1, K+1 ), LDA, WORK,
356 $ 1, ZERO, A( K+1, K-1 ), 1 )
357 A( K-1, K-1 ) = A( K-1, K-1 ) -
358 $ REAL( CDOTC( N-K, WORK, 1, A( K+1, K-1 ),
364 KP = ABS( IPIV( K ) )
367 * Interchange rows and columns K and KP in the trailing
368 * submatrix A(k-1:n,k-1:n)
371 $ CALL CSWAP( N-KP, A( KP+1, K ), 1, A( KP+1, KP ), 1 )
372 DO 70 J = K + 1, KP - 1
373 TEMP = CONJG( A( J, K ) )
374 A( J, K ) = CONJG( A( KP, J ) )
377 A( KP, K ) = CONJG( A( KP, K ) )
379 A( K, K ) = A( KP, KP )
381 IF( KSTEP.EQ.2 ) THEN
383 A( K, K-1 ) = A( KP, K-1 )