001:       SUBROUTINE CPPTRI( UPLO, N, AP, 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, N
010: *     ..
011: *     .. Array Arguments ..
012:       COMPLEX            AP( * )
013: *     ..
014: *
015: *  Purpose
016: *  =======
017: *
018: *  CPPTRI computes the inverse of a complex Hermitian positive definite
019: *  matrix A using the Cholesky factorization A = U**H*U or A = L*L**H
020: *  computed by CPPTRF.
021: *
022: *  Arguments
023: *  =========
024: *
025: *  UPLO    (input) CHARACTER*1
026: *          = 'U':  Upper triangular factor is stored in AP;
027: *          = 'L':  Lower triangular factor is stored in AP.
028: *
029: *  N       (input) INTEGER
030: *          The order of the matrix A.  N >= 0.
031: *
032: *  AP      (input/output) COMPLEX array, dimension (N*(N+1)/2)
033: *          On entry, the triangular factor U or L from the Cholesky
034: *          factorization A = U**H*U or A = L*L**H, packed columnwise as
035: *          a linear array.  The j-th column of U or L is stored in the
036: *          array AP as follows:
037: *          if UPLO = 'U', AP(i + (j-1)*j/2) = U(i,j) for 1<=i<=j;
038: *          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = L(i,j) for j<=i<=n.
039: *
040: *          On exit, the upper or lower triangle of the (Hermitian)
041: *          inverse of A, overwriting the input factor U or L.
042: *
043: *  INFO    (output) INTEGER
044: *          = 0:  successful exit
045: *          < 0:  if INFO = -i, the i-th argument had an illegal value
046: *          > 0:  if INFO = i, the (i,i) element of the factor U or L is
047: *                zero, and the inverse could not be computed.
048: *
049: *  =====================================================================
050: *
051: *     .. Parameters ..
052:       REAL               ONE
053:       PARAMETER          ( ONE = 1.0E+0 )
054: *     ..
055: *     .. Local Scalars ..
056:       LOGICAL            UPPER
057:       INTEGER            J, JC, JJ, JJN
058:       REAL               AJJ
059: *     ..
060: *     .. External Functions ..
061:       LOGICAL            LSAME
062:       COMPLEX            CDOTC
063:       EXTERNAL           LSAME, CDOTC
064: *     ..
065: *     .. External Subroutines ..
066:       EXTERNAL           CHPR, CSSCAL, CTPMV, CTPTRI, XERBLA
067: *     ..
068: *     .. Intrinsic Functions ..
069:       INTRINSIC          REAL
070: *     ..
071: *     .. Executable Statements ..
072: *
073: *     Test the input parameters.
074: *
075:       INFO = 0
076:       UPPER = LSAME( UPLO, 'U' )
077:       IF( .NOT.UPPER .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
078:          INFO = -1
079:       ELSE IF( N.LT.0 ) THEN
080:          INFO = -2
081:       END IF
082:       IF( INFO.NE.0 ) THEN
083:          CALL XERBLA( 'CPPTRI', -INFO )
084:          RETURN
085:       END IF
086: *
087: *     Quick return if possible
088: *
089:       IF( N.EQ.0 )
090:      $   RETURN
091: *
092: *     Invert the triangular Cholesky factor U or L.
093: *
094:       CALL CTPTRI( UPLO, 'Non-unit', N, AP, INFO )
095:       IF( INFO.GT.0 )
096:      $   RETURN
097:       IF( UPPER ) THEN
098: *
099: *        Compute the product inv(U) * inv(U)'.
100: *
101:          JJ = 0
102:          DO 10 J = 1, N
103:             JC = JJ + 1
104:             JJ = JJ + J
105:             IF( J.GT.1 )
106:      $         CALL CHPR( 'Upper', J-1, ONE, AP( JC ), 1, AP )
107:             AJJ = AP( JJ )
108:             CALL CSSCAL( J, AJJ, AP( JC ), 1 )
109:    10    CONTINUE
110: *
111:       ELSE
112: *
113: *        Compute the product inv(L)' * inv(L).
114: *
115:          JJ = 1
116:          DO 20 J = 1, N
117:             JJN = JJ + N - J + 1
118:             AP( JJ ) = REAL( CDOTC( N-J+1, AP( JJ ), 1, AP( JJ ), 1 ) )
119:             IF( J.LT.N )
120:      $         CALL CTPMV( 'Lower', 'Conjugate transpose', 'Non-unit',
121:      $                     N-J, AP( JJN ), AP( JJ+1 ), 1 )
122:             JJ = JJN
123:    20    CONTINUE
124:       END IF
125: *
126:       RETURN
127: *
128: *     End of CPPTRI
129: *
130:       END
131: