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

◆ ssytri()

subroutine ssytri ( character uplo,
integer n,
real, dimension( lda, * ) a,
integer lda,
integer, dimension( * ) ipiv,
real, dimension( * ) work,
integer info )

SSYTRI

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

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