LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ csytri()

subroutine csytri ( character uplo,
integer n,
complex, dimension( lda, * ) a,
integer lda,
integer, dimension( * ) ipiv,
complex, dimension( * ) work,
integer info )

CSYTRI

Download CSYTRI + dependencies [TGZ] [ZIP] [TXT]

Purpose:
!>
!> CSYTRI computes the inverse of a complex symmetric indefinite matrix
!> A using the factorization A = U*D*U**T or A = L*D*L**T computed by
!> CSYTRF.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          Specifies whether the details of the factorization are stored
!>          as an upper or lower triangular matrix.
!>          = 'U':  Upper triangular, form is A = U*D*U**T;
!>          = 'L':  Lower triangular, form is A = L*D*L**T.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in,out]A
!>          A is COMPLEX array, dimension (LDA,N)
!>          On entry, the block diagonal matrix D and the multipliers
!>          used to obtain the factor U or L as computed by CSYTRF.
!>
!>          On exit, if INFO = 0, the (symmetric) inverse of the original
!>          matrix.  If UPLO = 'U', the upper triangular part of the
!>          inverse is formed and the part of A below the diagonal is not
!>          referenced; if UPLO = 'L' the lower triangular part of the
!>          inverse is formed and the part of A above the diagonal is
!>          not referenced.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in]IPIV
!>          IPIV is INTEGER array, dimension (N)
!>          Details of the interchanges and the block structure of D
!>          as determined by CSYTRF.
!> 
[out]WORK
!>          WORK is COMPLEX array, dimension (2*N)
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0: successful exit
!>          < 0: if INFO = -i, the i-th argument had an illegal value
!>          > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
!>               inverse could not be computed.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 111 of file csytri.f.

112*
113* -- LAPACK computational routine --
114* -- LAPACK is a software package provided by Univ. of Tennessee, --
115* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
116*
117* .. Scalar Arguments ..
118 CHARACTER UPLO
119 INTEGER INFO, LDA, N
120* ..
121* .. Array Arguments ..
122 INTEGER IPIV( * )
123 COMPLEX A( LDA, * ), WORK( * )
124* ..
125*
126* =====================================================================
127*
128* .. Parameters ..
129 COMPLEX ONE, ZERO
130 parameter( one = ( 1.0e+0, 0.0e+0 ),
131 $ zero = ( 0.0e+0, 0.0e+0 ) )
132* ..
133* .. Local Scalars ..
134 LOGICAL UPPER
135 INTEGER K, KP, KSTEP
136 COMPLEX AK, AKKP1, AKP1, D, T, TEMP
137* ..
138* .. External Functions ..
139 LOGICAL LSAME
140 COMPLEX CDOTU
141 EXTERNAL lsame, cdotu
142* ..
143* .. External Subroutines ..
144 EXTERNAL ccopy, cswap, csymv, xerbla
145* ..
146* .. Intrinsic Functions ..
147 INTRINSIC abs, max
148* ..
149* .. Executable Statements ..
150*
151* Test the input parameters.
152*
153 info = 0
154 upper = lsame( uplo, 'U' )
155 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
156 info = -1
157 ELSE IF( n.LT.0 ) THEN
158 info = -2
159 ELSE IF( lda.LT.max( 1, n ) ) THEN
160 info = -4
161 END IF
162 IF( info.NE.0 ) THEN
163 CALL xerbla( 'CSYTRI', -info )
164 RETURN
165 END IF
166*
167* Quick return if possible
168*
169 IF( n.EQ.0 )
170 $ RETURN
171*
172* Check that the diagonal matrix D is nonsingular.
173*
174 IF( upper ) THEN
175*
176* Upper triangular storage: examine D from bottom to top
177*
178 DO 10 info = n, 1, -1
179 IF( ipiv( info ).GT.0 .AND. a( info, info ).EQ.zero )
180 $ RETURN
181 10 CONTINUE
182 ELSE
183*
184* Lower triangular storage: examine D from top to bottom.
185*
186 DO 20 info = 1, n
187 IF( ipiv( info ).GT.0 .AND. a( info, info ).EQ.zero )
188 $ RETURN
189 20 CONTINUE
190 END IF
191 info = 0
192*
193 IF( upper ) THEN
194*
195* Compute inv(A) from the factorization A = U*D*U**T.
196*
197* K is the main loop index, increasing from 1 to N in steps of
198* 1 or 2, depending on the size of the diagonal blocks.
199*
200 k = 1
201 30 CONTINUE
202*
203* If K > N, exit from loop.
204*
205 IF( k.GT.n )
206 $ GO TO 40
207*
208 IF( ipiv( k ).GT.0 ) THEN
209*
210* 1 x 1 diagonal block
211*
212* Invert the diagonal block.
213*
214 a( k, k ) = one / a( k, k )
215*
216* Compute column K of the inverse.
217*
218 IF( k.GT.1 ) THEN
219 CALL ccopy( k-1, a( 1, k ), 1, work, 1 )
220 CALL csymv( uplo, k-1, -one, a, lda, work, 1, zero,
221 $ a( 1, k ), 1 )
222 a( k, k ) = a( k, k ) - cdotu( k-1, work, 1, a( 1,
223 $ k ),
224 $ 1 )
225 END IF
226 kstep = 1
227 ELSE
228*
229* 2 x 2 diagonal block
230*
231* Invert the diagonal block.
232*
233 t = a( k, k+1 )
234 ak = a( k, k ) / t
235 akp1 = a( k+1, k+1 ) / t
236 akkp1 = a( k, k+1 ) / t
237 d = t*( ak*akp1-one )
238 a( k, k ) = akp1 / d
239 a( k+1, k+1 ) = ak / d
240 a( k, k+1 ) = -akkp1 / d
241*
242* Compute columns K and K+1 of the inverse.
243*
244 IF( k.GT.1 ) THEN
245 CALL ccopy( k-1, a( 1, k ), 1, work, 1 )
246 CALL csymv( uplo, k-1, -one, a, lda, work, 1, zero,
247 $ a( 1, k ), 1 )
248 a( k, k ) = a( k, k ) - cdotu( k-1, work, 1, a( 1,
249 $ k ),
250 $ 1 )
251 a( k, k+1 ) = a( k, k+1 ) -
252 $ cdotu( k-1, a( 1, k ), 1, a( 1, k+1 ),
253 $ 1 )
254 CALL ccopy( k-1, a( 1, k+1 ), 1, work, 1 )
255 CALL csymv( uplo, k-1, -one, a, lda, work, 1, zero,
256 $ a( 1, k+1 ), 1 )
257 a( k+1, k+1 ) = a( k+1, k+1 ) -
258 $ cdotu( k-1, work, 1, a( 1, k+1 ), 1 )
259 END IF
260 kstep = 2
261 END IF
262*
263 kp = abs( ipiv( k ) )
264 IF( kp.NE.k ) THEN
265*
266* Interchange rows and columns K and KP in the leading
267* submatrix A(1:k+1,1:k+1)
268*
269 CALL cswap( kp-1, a( 1, k ), 1, a( 1, kp ), 1 )
270 CALL cswap( k-kp-1, a( kp+1, k ), 1, a( kp, kp+1 ), lda )
271 temp = a( k, k )
272 a( k, k ) = a( kp, kp )
273 a( kp, kp ) = temp
274 IF( kstep.EQ.2 ) THEN
275 temp = a( k, k+1 )
276 a( k, k+1 ) = a( kp, k+1 )
277 a( kp, k+1 ) = temp
278 END IF
279 END IF
280*
281 k = k + kstep
282 GO TO 30
283 40 CONTINUE
284*
285 ELSE
286*
287* Compute inv(A) from the factorization A = L*D*L**T.
288*
289* K is the main loop index, increasing from 1 to N in steps of
290* 1 or 2, depending on the size of the diagonal blocks.
291*
292 k = n
293 50 CONTINUE
294*
295* If K < 1, exit from loop.
296*
297 IF( k.LT.1 )
298 $ GO TO 60
299*
300 IF( ipiv( k ).GT.0 ) THEN
301*
302* 1 x 1 diagonal block
303*
304* Invert the diagonal block.
305*
306 a( k, k ) = one / a( k, k )
307*
308* Compute column K of the inverse.
309*
310 IF( k.LT.n ) THEN
311 CALL ccopy( n-k, a( k+1, k ), 1, work, 1 )
312 CALL csymv( uplo, n-k, -one, a( k+1, k+1 ), lda, work,
313 $ 1,
314 $ zero, a( k+1, k ), 1 )
315 a( k, k ) = a( k, k ) - cdotu( n-k, work, 1, a( k+1,
316 $ k ),
317 $ 1 )
318 END IF
319 kstep = 1
320 ELSE
321*
322* 2 x 2 diagonal block
323*
324* Invert the diagonal block.
325*
326 t = a( k, k-1 )
327 ak = a( k-1, k-1 ) / t
328 akp1 = a( k, k ) / t
329 akkp1 = a( k, k-1 ) / t
330 d = t*( ak*akp1-one )
331 a( k-1, k-1 ) = akp1 / d
332 a( k, k ) = ak / d
333 a( k, k-1 ) = -akkp1 / d
334*
335* Compute columns K-1 and K of the inverse.
336*
337 IF( k.LT.n ) THEN
338 CALL ccopy( n-k, a( k+1, k ), 1, work, 1 )
339 CALL csymv( uplo, n-k, -one, a( k+1, k+1 ), lda, work,
340 $ 1,
341 $ zero, a( k+1, k ), 1 )
342 a( k, k ) = a( k, k ) - cdotu( n-k, work, 1, a( k+1,
343 $ k ),
344 $ 1 )
345 a( k, k-1 ) = a( k, k-1 ) -
346 $ cdotu( n-k, a( k+1, k ), 1, a( k+1,
347 $ k-1 ),
348 $ 1 )
349 CALL ccopy( n-k, a( k+1, k-1 ), 1, work, 1 )
350 CALL csymv( uplo, n-k, -one, a( k+1, k+1 ), lda, work,
351 $ 1,
352 $ zero, a( k+1, k-1 ), 1 )
353 a( k-1, k-1 ) = a( k-1, k-1 ) -
354 $ cdotu( n-k, work, 1, a( k+1, k-1 ),
355 $ 1 )
356 END IF
357 kstep = 2
358 END IF
359*
360 kp = abs( ipiv( k ) )
361 IF( kp.NE.k ) THEN
362*
363* Interchange rows and columns K and KP in the trailing
364* submatrix A(k-1:n,k-1:n)
365*
366 IF( kp.LT.n )
367 $ CALL cswap( n-kp, a( kp+1, k ), 1, a( kp+1, kp ), 1 )
368 CALL cswap( kp-k-1, a( k+1, k ), 1, a( kp, k+1 ), lda )
369 temp = a( k, k )
370 a( k, k ) = a( kp, kp )
371 a( kp, kp ) = temp
372 IF( kstep.EQ.2 ) THEN
373 temp = a( k, k-1 )
374 a( k, k-1 ) = a( kp, k-1 )
375 a( kp, k-1 ) = temp
376 END IF
377 END IF
378*
379 k = k - kstep
380 GO TO 50
381 60 CONTINUE
382 END IF
383*
384 RETURN
385*
386* End of CSYTRI
387*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ccopy(n, cx, incx, cy, incy)
CCOPY
Definition ccopy.f:81
complex function cdotu(n, cx, incx, cy, incy)
CDOTU
Definition cdotu.f:83
subroutine csymv(uplo, n, alpha, a, lda, x, incx, beta, y, incy)
CSYMV computes a matrix-vector product for a complex symmetric matrix.
Definition csymv.f:156
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine cswap(n, cx, incx, cy, incy)
CSWAP
Definition cswap.f:81
Here is the call graph for this function:
Here is the caller graph for this function: