LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zpptri ( character  UPLO,
integer  N,
complex*16, dimension( * )  AP,
integer  INFO 
)

ZPPTRI

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

Purpose:
 ZPPTRI computes the inverse of a complex Hermitian positive definite
 matrix A using the Cholesky factorization A = U**H*U or A = L*L**H
 computed by ZPPTRF.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          = 'U':  Upper triangular factor is stored in AP;
          = 'L':  Lower triangular factor is stored in AP.
[in]N
          N is INTEGER
          The order of the matrix A.  N >= 0.
[in,out]AP
          AP is COMPLEX*16 array, dimension (N*(N+1)/2)
          On entry, the triangular factor U or L from the Cholesky
          factorization A = U**H*U or A = L*L**H, packed columnwise as
          a linear array.  The j-th column of U or L is stored in the
          array AP as follows:
          if UPLO = 'U', AP(i + (j-1)*j/2) = U(i,j) for 1<=i<=j;
          if UPLO = 'L', AP(i + (j-1)*(2n-j)/2) = L(i,j) for j<=i<=n.

          On exit, the upper or lower triangle of the (Hermitian)
          inverse of A, overwriting the input factor U or L.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
          > 0:  if INFO = i, the (i,i) element of the factor U or L is
                zero, and the inverse could not be computed.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 95 of file zpptri.f.

95 *
96 * -- LAPACK computational routine (version 3.4.0) --
97 * -- LAPACK is a software package provided by Univ. of Tennessee, --
98 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
99 * November 2011
100 *
101 * .. Scalar Arguments ..
102  CHARACTER uplo
103  INTEGER info, n
104 * ..
105 * .. Array Arguments ..
106  COMPLEX*16 ap( * )
107 * ..
108 *
109 * =====================================================================
110 *
111 * .. Parameters ..
112  DOUBLE PRECISION one
113  parameter ( one = 1.0d+0 )
114 * ..
115 * .. Local Scalars ..
116  LOGICAL upper
117  INTEGER j, jc, jj, jjn
118  DOUBLE PRECISION ajj
119 * ..
120 * .. External Functions ..
121  LOGICAL lsame
122  COMPLEX*16 zdotc
123  EXTERNAL lsame, zdotc
124 * ..
125 * .. External Subroutines ..
126  EXTERNAL xerbla, zdscal, zhpr, ztpmv, ztptri
127 * ..
128 * .. Intrinsic Functions ..
129  INTRINSIC dble
130 * ..
131 * .. Executable Statements ..
132 *
133 * Test the input parameters.
134 *
135  info = 0
136  upper = lsame( uplo, 'U' )
137  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
138  info = -1
139  ELSE IF( n.LT.0 ) THEN
140  info = -2
141  END IF
142  IF( info.NE.0 ) THEN
143  CALL xerbla( 'ZPPTRI', -info )
144  RETURN
145  END IF
146 *
147 * Quick return if possible
148 *
149  IF( n.EQ.0 )
150  $ RETURN
151 *
152 * Invert the triangular Cholesky factor U or L.
153 *
154  CALL ztptri( uplo, 'Non-unit', n, ap, info )
155  IF( info.GT.0 )
156  $ RETURN
157  IF( upper ) THEN
158 *
159 * Compute the product inv(U) * inv(U)**H.
160 *
161  jj = 0
162  DO 10 j = 1, n
163  jc = jj + 1
164  jj = jj + j
165  IF( j.GT.1 )
166  $ CALL zhpr( 'Upper', j-1, one, ap( jc ), 1, ap )
167  ajj = ap( jj )
168  CALL zdscal( j, ajj, ap( jc ), 1 )
169  10 CONTINUE
170 *
171  ELSE
172 *
173 * Compute the product inv(L)**H * inv(L).
174 *
175  jj = 1
176  DO 20 j = 1, n
177  jjn = jj + n - j + 1
178  ap( jj ) = dble( zdotc( n-j+1, ap( jj ), 1, ap( jj ), 1 ) )
179  IF( j.LT.n )
180  $ CALL ztpmv( 'Lower', 'Conjugate transpose', 'Non-unit',
181  $ n-j, ap( jjn ), ap( jj+1 ), 1 )
182  jj = jjn
183  20 CONTINUE
184  END IF
185 *
186  RETURN
187 *
188 * End of ZPPTRI
189 *
subroutine ztptri(UPLO, DIAG, N, AP, INFO)
ZTPTRI
Definition: ztptri.f:119
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
complex *16 function zdotc(N, ZX, INCX, ZY, INCY)
ZDOTC
Definition: zdotc.f:54
subroutine ztpmv(UPLO, TRANS, DIAG, N, AP, X, INCX)
ZTPMV
Definition: ztpmv.f:144
subroutine zhpr(UPLO, N, ALPHA, X, INCX, AP)
ZHPR
Definition: zhpr.f:132
subroutine zdscal(N, DA, ZX, INCX)
ZDSCAL
Definition: zdscal.f:54
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: