001:       SUBROUTINE SSYTRI( UPLO, N, A, LDA, IPIV, WORK, INFO )
002: *
003: *  -- LAPACK routine (version 3.2) --
004: *     Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd..
005: *     November 2006
006: *
007: *     .. Scalar Arguments ..
008:       CHARACTER          UPLO
009:       INTEGER            INFO, LDA, N
010: *     ..
011: *     .. Array Arguments ..
012:       INTEGER            IPIV( * )
013:       REAL               A( LDA, * ), WORK( * )
014: *     ..
015: *
016: *  Purpose
017: *  =======
018: *
019: *  SSYTRI computes the inverse of a real symmetric indefinite matrix
020: *  A using the factorization A = U*D*U**T or A = L*D*L**T computed by
021: *  SSYTRF.
022: *
023: *  Arguments
024: *  =========
025: *
026: *  UPLO    (input) CHARACTER*1
027: *          Specifies whether the details of the factorization are stored
028: *          as an upper or lower triangular matrix.
029: *          = 'U':  Upper triangular, form is A = U*D*U**T;
030: *          = 'L':  Lower triangular, form is A = L*D*L**T.
031: *
032: *  N       (input) INTEGER
033: *          The order of the matrix A.  N >= 0.
034: *
035: *  A       (input/output) REAL array, dimension (LDA,N)
036: *          On entry, the block diagonal matrix D and the multipliers
037: *          used to obtain the factor U or L as computed by SSYTRF.
038: *
039: *          On exit, if INFO = 0, the (symmetric) inverse of the original
040: *          matrix.  If UPLO = 'U', the upper triangular part of the
041: *          inverse is formed and the part of A below the diagonal is not
042: *          referenced; if UPLO = 'L' the lower triangular part of the
043: *          inverse is formed and the part of A above the diagonal is
044: *          not referenced.
045: *
046: *  LDA     (input) INTEGER
047: *          The leading dimension of the array A.  LDA >= max(1,N).
048: *
049: *  IPIV    (input) INTEGER array, dimension (N)
050: *          Details of the interchanges and the block structure of D
051: *          as determined by SSYTRF.
052: *
053: *  WORK    (workspace) REAL array, dimension (N)
054: *
055: *  INFO    (output) INTEGER
056: *          = 0: successful exit
057: *          < 0: if INFO = -i, the i-th argument had an illegal value
058: *          > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
059: *               inverse could not be computed.
060: *
061: *  =====================================================================
062: *
063: *     .. Parameters ..
064:       REAL               ONE, ZERO
065:       PARAMETER          ( ONE = 1.0E+0, ZERO = 0.0E+0 )
066: *     ..
067: *     .. Local Scalars ..
068:       LOGICAL            UPPER
069:       INTEGER            K, KP, KSTEP
070:       REAL               AK, AKKP1, AKP1, D, T, TEMP
071: *     ..
072: *     .. External Functions ..
073:       LOGICAL            LSAME
074:       REAL               SDOT
075:       EXTERNAL           LSAME, SDOT
076: *     ..
077: *     .. External Subroutines ..
078:       EXTERNAL           SCOPY, SSWAP, SSYMV, XERBLA
079: *     ..
080: *     .. Intrinsic Functions ..
081:       INTRINSIC          ABS, MAX
082: *     ..
083: *     .. Executable Statements ..
084: *
085: *     Test the input parameters.
086: *
087:       INFO = 0
088:       UPPER = LSAME( UPLO, 'U' )
089:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
090:          INFO = -1
091:       ELSE IF( N.LT.0 ) THEN
092:          INFO = -2
093:       ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
094:          INFO = -4
095:       END IF
096:       IF( INFO.NE.0 ) THEN
097:          CALL XERBLA( 'SSYTRI', -INFO )
098:          RETURN
099:       END IF
100: *
101: *     Quick return if possible
102: *
103:       IF( N.EQ.0 )
104:      $   RETURN
105: *
106: *     Check that the diagonal matrix D is nonsingular.
107: *
108:       IF( UPPER ) THEN
109: *
110: *        Upper triangular storage: examine D from bottom to top
111: *
112:          DO 10 INFO = N, 1, -1
113:             IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.ZERO )
114:      $         RETURN
115:    10    CONTINUE
116:       ELSE
117: *
118: *        Lower triangular storage: examine D from top to bottom.
119: *
120:          DO 20 INFO = 1, N
121:             IF( IPIV( INFO ).GT.0 .AND. A( INFO, INFO ).EQ.ZERO )
122:      $         RETURN
123:    20    CONTINUE
124:       END IF
125:       INFO = 0
126: *
127:       IF( UPPER ) THEN
128: *
129: *        Compute inv(A) from the factorization A = U*D*U'.
130: *
131: *        K is the main loop index, increasing from 1 to N in steps of
132: *        1 or 2, depending on the size of the diagonal blocks.
133: *
134:          K = 1
135:    30    CONTINUE
136: *
137: *        If K > N, exit from loop.
138: *
139:          IF( K.GT.N )
140:      $      GO TO 40
141: *
142:          IF( IPIV( K ).GT.0 ) THEN
143: *
144: *           1 x 1 diagonal block
145: *
146: *           Invert the diagonal block.
147: *
148:             A( K, K ) = ONE / A( K, K )
149: *
150: *           Compute column K of the inverse.
151: *
152:             IF( K.GT.1 ) THEN
153:                CALL SCOPY( K-1, A( 1, K ), 1, WORK, 1 )
154:                CALL SSYMV( UPLO, K-1, -ONE, A, LDA, WORK, 1, ZERO,
155:      $                     A( 1, K ), 1 )
156:                A( K, K ) = A( K, K ) - SDOT( K-1, WORK, 1, A( 1, K ),
157:      $                     1 )
158:             END IF
159:             KSTEP = 1
160:          ELSE
161: *
162: *           2 x 2 diagonal block
163: *
164: *           Invert the diagonal block.
165: *
166:             T = ABS( A( K, K+1 ) )
167:             AK = A( K, K ) / T
168:             AKP1 = A( K+1, K+1 ) / T
169:             AKKP1 = A( K, K+1 ) / T
170:             D = T*( AK*AKP1-ONE )
171:             A( K, K ) = AKP1 / D
172:             A( K+1, K+1 ) = AK / D
173:             A( K, K+1 ) = -AKKP1 / D
174: *
175: *           Compute columns K and K+1 of the inverse.
176: *
177:             IF( K.GT.1 ) THEN
178:                CALL SCOPY( K-1, A( 1, K ), 1, WORK, 1 )
179:                CALL SSYMV( UPLO, K-1, -ONE, A, LDA, WORK, 1, ZERO,
180:      $                     A( 1, K ), 1 )
181:                A( K, K ) = A( K, K ) - SDOT( K-1, WORK, 1, A( 1, K ),
182:      $                     1 )
183:                A( K, K+1 ) = A( K, K+1 ) -
184:      $                       SDOT( K-1, A( 1, K ), 1, A( 1, K+1 ), 1 )
185:                CALL SCOPY( K-1, A( 1, K+1 ), 1, WORK, 1 )
186:                CALL SSYMV( UPLO, K-1, -ONE, A, LDA, WORK, 1, ZERO,
187:      $                     A( 1, K+1 ), 1 )
188:                A( K+1, K+1 ) = A( K+1, K+1 ) -
189:      $                         SDOT( K-1, WORK, 1, A( 1, K+1 ), 1 )
190:             END IF
191:             KSTEP = 2
192:          END IF
193: *
194:          KP = ABS( IPIV( K ) )
195:          IF( KP.NE.K ) THEN
196: *
197: *           Interchange rows and columns K and KP in the leading
198: *           submatrix A(1:k+1,1:k+1)
199: *
200:             CALL SSWAP( KP-1, A( 1, K ), 1, A( 1, KP ), 1 )
201:             CALL SSWAP( K-KP-1, A( KP+1, K ), 1, A( KP, KP+1 ), LDA )
202:             TEMP = A( K, K )
203:             A( K, K ) = A( KP, KP )
204:             A( KP, KP ) = TEMP
205:             IF( KSTEP.EQ.2 ) THEN
206:                TEMP = A( K, K+1 )
207:                A( K, K+1 ) = A( KP, K+1 )
208:                A( KP, K+1 ) = TEMP
209:             END IF
210:          END IF
211: *
212:          K = K + KSTEP
213:          GO TO 30
214:    40    CONTINUE
215: *
216:       ELSE
217: *
218: *        Compute inv(A) from the factorization A = L*D*L'.
219: *
220: *        K is the main loop index, increasing from 1 to N in steps of
221: *        1 or 2, depending on the size of the diagonal blocks.
222: *
223:          K = N
224:    50    CONTINUE
225: *
226: *        If K < 1, exit from loop.
227: *
228:          IF( K.LT.1 )
229:      $      GO TO 60
230: *
231:          IF( IPIV( K ).GT.0 ) THEN
232: *
233: *           1 x 1 diagonal block
234: *
235: *           Invert the diagonal block.
236: *
237:             A( K, K ) = ONE / A( K, K )
238: *
239: *           Compute column K of the inverse.
240: *
241:             IF( K.LT.N ) THEN
242:                CALL SCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
243:                CALL SSYMV( UPLO, N-K, -ONE, A( K+1, K+1 ), LDA, WORK, 1,
244:      $                     ZERO, A( K+1, K ), 1 )
245:                A( K, K ) = A( K, K ) - SDOT( N-K, WORK, 1, A( K+1, K ),
246:      $                     1 )
247:             END IF
248:             KSTEP = 1
249:          ELSE
250: *
251: *           2 x 2 diagonal block
252: *
253: *           Invert the diagonal block.
254: *
255:             T = ABS( A( K, K-1 ) )
256:             AK = A( K-1, K-1 ) / T
257:             AKP1 = A( K, K ) / T
258:             AKKP1 = A( K, K-1 ) / T
259:             D = T*( AK*AKP1-ONE )
260:             A( K-1, K-1 ) = AKP1 / D
261:             A( K, K ) = AK / D
262:             A( K, K-1 ) = -AKKP1 / D
263: *
264: *           Compute columns K-1 and K of the inverse.
265: *
266:             IF( K.LT.N ) THEN
267:                CALL SCOPY( N-K, A( K+1, K ), 1, WORK, 1 )
268:                CALL SSYMV( UPLO, N-K, -ONE, A( K+1, K+1 ), LDA, WORK, 1,
269:      $                     ZERO, A( K+1, K ), 1 )
270:                A( K, K ) = A( K, K ) - SDOT( N-K, WORK, 1, A( K+1, K ),
271:      $                     1 )
272:                A( K, K-1 ) = A( K, K-1 ) -
273:      $                       SDOT( N-K, A( K+1, K ), 1, A( K+1, K-1 ),
274:      $                       1 )
275:                CALL SCOPY( N-K, A( K+1, K-1 ), 1, WORK, 1 )
276:                CALL SSYMV( UPLO, N-K, -ONE, A( K+1, K+1 ), LDA, WORK, 1,
277:      $                     ZERO, A( K+1, K-1 ), 1 )
278:                A( K-1, K-1 ) = A( K-1, K-1 ) -
279:      $                         SDOT( N-K, WORK, 1, A( K+1, K-1 ), 1 )
280:             END IF
281:             KSTEP = 2
282:          END IF
283: *
284:          KP = ABS( IPIV( K ) )
285:          IF( KP.NE.K ) THEN
286: *
287: *           Interchange rows and columns K and KP in the trailing
288: *           submatrix A(k-1:n,k-1:n)
289: *
290:             IF( KP.LT.N )
291:      $         CALL SSWAP( N-KP, A( KP+1, K ), 1, A( KP+1, KP ), 1 )
292:             CALL SSWAP( KP-K-1, A( K+1, K ), 1, A( KP, K+1 ), LDA )
293:             TEMP = A( K, K )
294:             A( K, K ) = A( KP, KP )
295:             A( KP, KP ) = TEMP
296:             IF( KSTEP.EQ.2 ) THEN
297:                TEMP = A( K, K-1 )
298:                A( K, K-1 ) = A( KP, K-1 )
299:                A( KP, K-1 ) = TEMP
300:             END IF
301:          END IF
302: *
303:          K = K - KSTEP
304:          GO TO 50
305:    60    CONTINUE
306:       END IF
307: *
308:       RETURN
309: *
310: *     End of SSYTRI
311: *
312:       END
313: