3 * =========== DOCUMENTATION ===========
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
9 *> Download ZSYTRI + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zsytri.f">
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zsytri.f">
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsytri.f">
21 * SUBROUTINE ZSYTRI( UPLO, N, A, LDA, IPIV, WORK, INFO )
23 * .. Scalar Arguments ..
25 * INTEGER INFO, LDA, N
27 * .. Array Arguments ..
29 * COMPLEX*16 A( LDA, * ), WORK( * )
38 *> ZSYTRI computes the inverse of a complex symmetric indefinite matrix
39 *> A using the factorization A = U*D*U**T or A = L*D*L**T 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**T;
52 *> = 'L': Lower triangular, form is A = L*D*L**T.
58 *> The order of the matrix A. N >= 0.
63 *> A is COMPLEX*16 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 ZSYTRF.
67 *> On exit, if INFO = 0, the (symmetric) 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 ZSYTRF.
90 *> WORK is COMPLEX*16 array, dimension (2*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 complex16SYcomputational
114 * =====================================================================
115 SUBROUTINE ZSYTRI( 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*16 A( LDA, * ), WORK( * )
131 * =====================================================================
135 PARAMETER ( ONE = ( 1.0D+0, 0.0D+0 ),
136 $ ZERO = ( 0.0D+0, 0.0D+0 ) )
138 * .. Local Scalars ..
141 COMPLEX*16 AK, AKKP1, AKP1, D, T, TEMP
143 * .. External Functions ..
146 EXTERNAL LSAME, ZDOTU
148 * .. External Subroutines ..
149 EXTERNAL XERBLA, ZCOPY, ZSWAP, ZSYMV
151 * .. Intrinsic Functions ..
154 * .. Executable Statements ..
156 * Test the input parameters.
159 UPPER = LSAME( UPLO, 'U' )
160 IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
162 ELSE IF( N.LT.0 ) THEN
164 ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
168 CALL XERBLA( 'ZSYTRI', -INFO )
172 * Quick return if possible
177 * Check that the diagonal matrix D is nonsingular.
181 * Upper triangular storage: examine D from bottom to top
183 DO 10 INFO = N, 1, -1
184 IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.ZERO )
189 * Lower triangular storage: examine D from top to bottom.
192 IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.ZERO )
200 * Compute inv(A) from the factorization A = U*D*U**T.
202 * K is the main loop index, increasing from 1 to N in steps of
203 * 1 or 2, depending on the size of the diagonal blocks.
208 * If K > N, exit from loop.
213 IF( IPIV( K ).GT.0 ) THEN
215 * 1 x 1 diagonal block
217 * Invert the diagonal block.
219 A( K, K ) = ONE / A( K, K )
221 * Compute column K of the inverse.
224 CALL ZCOPY( K-1, A( 1, K ), 1, WORK, 1 )
225 CALL ZSYMV( UPLO, K-1, -ONE, A, LDA, WORK, 1, ZERO,
227 A( K, K ) = A( K, K ) - ZDOTU( K-1, WORK, 1, A( 1, K ),
233 * 2 x 2 diagonal block
235 * Invert the diagonal block.
239 AKP1 = A( K+1, K+1 ) / T
240 AKKP1 = A( K, K+1 ) / T
241 D = T*( AK*AKP1-ONE )
243 A( K+1, K+1 ) = AK / D
244 A( K, K+1 ) = -AKKP1 / D
246 * Compute columns K and K+1 of the inverse.
249 CALL ZCOPY( K-1, A( 1, K ), 1, WORK, 1 )
250 CALL ZSYMV( UPLO, K-1, -ONE, A, LDA, WORK, 1, ZERO,
252 A( K, K ) = A( K, K ) - ZDOTU( K-1, WORK, 1, A( 1, K ),
254 A( K, K+1 ) = A( K, K+1 ) -
255 $ ZDOTU( K-1, A( 1, K ), 1, A( 1, K+1 ), 1 )
256 CALL ZCOPY( K-1, A( 1, K+1 ), 1, WORK, 1 )
257 CALL ZSYMV( UPLO, K-1, -ONE, A, LDA, WORK, 1, ZERO,
259 A( K+1, K+1 ) = A( K+1, K+1 ) -
260 $ ZDOTU( K-1, WORK, 1, A( 1, K+1 ), 1 )
265 KP = ABS( IPIV( K ) )
268 * Interchange rows and columns K and KP in the leading
269 * submatrix A(1:k+1,1:k+1)
271 CALL ZSWAP( KP-1, A( 1, K ), 1, A( 1, KP ), 1 )
272 CALL ZSWAP( K-KP-1, A( KP+1, K ), 1, A( KP, KP+1 ), LDA )
274 A( K, K ) = A( KP, KP )
276 IF( KSTEP.EQ.2 ) THEN
278 A( K, K+1 ) = A( KP, K+1 )
289 * Compute inv(A) from the factorization A = L*D*L**T.
291 * K is the main loop index, increasing from 1 to N in steps of
292 * 1 or 2, depending on the size of the diagonal blocks.
297 * If K < 1, exit from loop.
302 IF( IPIV( K ).GT.0 ) THEN
304 * 1 x 1 diagonal block
306 * Invert the diagonal block.
308 A( K, K ) = ONE / A( K, K )
310 * Compute column K of the inverse.
313 CALL ZCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
314 CALL ZSYMV( UPLO, N-K, -ONE, A( K+1, K+1 ), LDA, WORK, 1,
315 $ ZERO, A( K+1, K ), 1 )
316 A( K, K ) = A( K, K ) - ZDOTU( N-K, WORK, 1, A( K+1, K ),
322 * 2 x 2 diagonal block
324 * Invert the diagonal block.
327 AK = A( K-1, K-1 ) / T
329 AKKP1 = A( K, K-1 ) / T
330 D = T*( AK*AKP1-ONE )
331 A( K-1, K-1 ) = AKP1 / D
333 A( K, K-1 ) = -AKKP1 / D
335 * Compute columns K-1 and K of the inverse.
338 CALL ZCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
339 CALL ZSYMV( UPLO, N-K, -ONE, A( K+1, K+1 ), LDA, WORK, 1,
340 $ ZERO, A( K+1, K ), 1 )
341 A( K, K ) = A( K, K ) - ZDOTU( N-K, WORK, 1, A( K+1, K ),
343 A( K, K-1 ) = A( K, K-1 ) -
344 $ ZDOTU( N-K, A( K+1, K ), 1, A( K+1, K-1 ),
346 CALL ZCOPY( N-K, A( K+1, K-1 ), 1, WORK, 1 )
347 CALL ZSYMV( UPLO, N-K, -ONE, A( K+1, K+1 ), LDA, WORK, 1,
348 $ ZERO, A( K+1, K-1 ), 1 )
349 A( K-1, K-1 ) = A( K-1, K-1 ) -
350 $ ZDOTU( N-K, WORK, 1, A( K+1, K-1 ), 1 )
355 KP = ABS( IPIV( K ) )
358 * Interchange rows and columns K and KP in the trailing
359 * submatrix A(k-1:n,k-1:n)
362 $ CALL ZSWAP( N-KP, A( KP+1, K ), 1, A( KP+1, KP ), 1 )
363 CALL ZSWAP( KP-K-1, A( K+1, K ), 1, A( KP, K+1 ), LDA )
365 A( K, K ) = A( KP, KP )
367 IF( KSTEP.EQ.2 ) THEN
369 A( K, K-1 ) = A( KP, K-1 )