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

◆ ctptri()

subroutine ctptri ( character  uplo,
character  diag,
integer  n,
complex, dimension( * )  ap,
integer  info 
)

CTPTRI

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

Purpose:
 CTPTRI 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 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 116 of file ctptri.f.

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