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

ZTPTRI

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

Purpose:
 ZTPTRI computes the inverse of a complex upper or lower triangular
 matrix A stored in packed format.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          = 'U':  A is upper triangular;
          = 'L':  A is lower triangular.
[in]DIAG
          DIAG is CHARACTER*1
          = 'N':  A is non-unit triangular;
          = 'U':  A is unit triangular.
[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 upper or lower triangular matrix A, stored
          columnwise in a linear array.  The j-th column of A is stored
          in the array AP as follows:
          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
          if UPLO = 'L', AP(i + (j-1)*((2*n-j)/2) = A(i,j) for j<=i<=n.
          See below for further details.
          On exit, the (triangular) inverse of the original matrix, in
          the same packed storage format.
[out]INFO
          INFO is INTEGER
          = 0:  successful exit
          < 0:  if INFO = -i, the i-th argument had an illegal value
          > 0:  if INFO = i, A(i,i) is exactly zero.  The triangular
                matrix is singular and its inverse can not be computed.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011
Further Details:
  A triangular matrix A can be transferred to packed storage using one
  of the following program segments:

  UPLO = 'U':                      UPLO = 'L':

        JC = 1                           JC = 1
        DO 2 J = 1, N                    DO 2 J = 1, N
           DO 1 I = 1, J                    DO 1 I = J, N
              AP(JC+I-1) = A(I,J)              AP(JC+I-J) = A(I,J)
      1    CONTINUE                    1    CONTINUE
           JC = JC + J                      JC = JC + N - J + 1
      2 CONTINUE                       2 CONTINUE

Definition at line 119 of file ztptri.f.

119 *
120 * -- LAPACK computational routine (version 3.4.0) --
121 * -- LAPACK is a software package provided by Univ. of Tennessee, --
122 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
123 * November 2011
124 *
125 * .. Scalar Arguments ..
126  CHARACTER diag, uplo
127  INTEGER info, n
128 * ..
129 * .. Array Arguments ..
130  COMPLEX*16 ap( * )
131 * ..
132 *
133 * =====================================================================
134 *
135 * .. Parameters ..
136  COMPLEX*16 one, zero
137  parameter ( one = ( 1.0d+0, 0.0d+0 ),
138  $ zero = ( 0.0d+0, 0.0d+0 ) )
139 * ..
140 * .. Local Scalars ..
141  LOGICAL nounit, upper
142  INTEGER j, jc, jclast, jj
143  COMPLEX*16 ajj
144 * ..
145 * .. External Functions ..
146  LOGICAL lsame
147  EXTERNAL lsame
148 * ..
149 * .. External Subroutines ..
150  EXTERNAL xerbla, zscal, ztpmv
151 * ..
152 * .. Executable Statements ..
153 *
154 * Test the input parameters.
155 *
156  info = 0
157  upper = lsame( uplo, 'U' )
158  nounit = lsame( diag, 'N' )
159  IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
160  info = -1
161  ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
162  info = -2
163  ELSE IF( n.LT.0 ) THEN
164  info = -3
165  END IF
166  IF( info.NE.0 ) THEN
167  CALL xerbla( 'ZTPTRI', -info )
168  RETURN
169  END IF
170 *
171 * Check for singularity if non-unit.
172 *
173  IF( nounit ) THEN
174  IF( upper ) THEN
175  jj = 0
176  DO 10 info = 1, n
177  jj = jj + info
178  IF( ap( jj ).EQ.zero )
179  $ RETURN
180  10 CONTINUE
181  ELSE
182  jj = 1
183  DO 20 info = 1, n
184  IF( ap( jj ).EQ.zero )
185  $ RETURN
186  jj = jj + n - info + 1
187  20 CONTINUE
188  END IF
189  info = 0
190  END IF
191 *
192  IF( upper ) THEN
193 *
194 * Compute inverse of upper triangular matrix.
195 *
196  jc = 1
197  DO 30 j = 1, n
198  IF( nounit ) THEN
199  ap( jc+j-1 ) = one / ap( jc+j-1 )
200  ajj = -ap( jc+j-1 )
201  ELSE
202  ajj = -one
203  END IF
204 *
205 * Compute elements 1:j-1 of j-th column.
206 *
207  CALL ztpmv( 'Upper', 'No transpose', diag, j-1, ap,
208  $ ap( jc ), 1 )
209  CALL zscal( j-1, ajj, ap( jc ), 1 )
210  jc = jc + j
211  30 CONTINUE
212 *
213  ELSE
214 *
215 * Compute inverse of lower triangular matrix.
216 *
217  jc = n*( n+1 ) / 2
218  DO 40 j = n, 1, -1
219  IF( nounit ) THEN
220  ap( jc ) = one / ap( jc )
221  ajj = -ap( jc )
222  ELSE
223  ajj = -one
224  END IF
225  IF( j.LT.n ) THEN
226 *
227 * Compute elements j+1:n of j-th column.
228 *
229  CALL ztpmv( 'Lower', 'No transpose', diag, n-j,
230  $ ap( jclast ), ap( jc+1 ), 1 )
231  CALL zscal( n-j, ajj, ap( jc+1 ), 1 )
232  END IF
233  jclast = jc
234  jc = jc - n + j - 2
235  40 CONTINUE
236  END IF
237 *
238  RETURN
239 *
240 * End of ZTPTRI
241 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine ztpmv(UPLO, TRANS, DIAG, N, AP, X, INCX)
ZTPMV
Definition: ztpmv.f:144
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine zscal(N, ZA, ZX, INCX)
ZSCAL
Definition: zscal.f:54

Here is the call graph for this function:

Here is the caller graph for this function: