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

◆ ztptri()

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.
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 114 of file ztptri.f.

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