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

◆ ctrtri()

subroutine ctrtri ( character  uplo,
character  diag,
integer  n,
complex, dimension( lda, * )  a,
integer  lda,
integer  info 
)

CTRTRI

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

Purpose:
 CTRTRI computes the inverse of a complex upper or lower triangular
 matrix A.

 This is the Level 3 BLAS version of the algorithm.
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]A
          A is COMPLEX array, dimension (LDA,N)
          On entry, the triangular matrix A.  If UPLO = 'U', the
          leading N-by-N upper triangular part of the array A contains
          the upper triangular matrix, and the strictly lower
          triangular part of A is not referenced.  If UPLO = 'L', the
          leading N-by-N lower triangular part of the array A contains
          the lower triangular matrix, and the strictly upper
          triangular part of A is not referenced.  If DIAG = 'U', the
          diagonal elements of A are also not referenced and are
          assumed to be 1.
          On exit, the (triangular) inverse of the original matrix, in
          the same storage format.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[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.

Definition at line 108 of file ctrtri.f.

109*
110* -- LAPACK computational routine --
111* -- LAPACK is a software package provided by Univ. of Tennessee, --
112* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
113*
114* .. Scalar Arguments ..
115 CHARACTER DIAG, UPLO
116 INTEGER INFO, LDA, N
117* ..
118* .. Array Arguments ..
119 COMPLEX A( LDA, * )
120* ..
121*
122* =====================================================================
123*
124* .. Parameters ..
125 COMPLEX ONE, ZERO
126 parameter( one = ( 1.0e+0, 0.0e+0 ),
127 $ zero = ( 0.0e+0, 0.0e+0 ) )
128* ..
129* .. Local Scalars ..
130 LOGICAL NOUNIT, UPPER
131 INTEGER J, JB, NB, NN
132* ..
133* .. External Functions ..
134 LOGICAL LSAME
135 INTEGER ILAENV
136 EXTERNAL lsame, ilaenv
137* ..
138* .. External Subroutines ..
139 EXTERNAL ctrmm, ctrsm, ctrti2, xerbla
140* ..
141* .. Intrinsic Functions ..
142 INTRINSIC max, min
143* ..
144* .. Executable Statements ..
145*
146* Test the input parameters.
147*
148 info = 0
149 upper = lsame( uplo, 'U' )
150 nounit = lsame( diag, 'N' )
151 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
152 info = -1
153 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
154 info = -2
155 ELSE IF( n.LT.0 ) THEN
156 info = -3
157 ELSE IF( lda.LT.max( 1, n ) ) THEN
158 info = -5
159 END IF
160 IF( info.NE.0 ) THEN
161 CALL xerbla( 'CTRTRI', -info )
162 RETURN
163 END IF
164*
165* Quick return if possible
166*
167 IF( n.EQ.0 )
168 $ RETURN
169*
170* Check for singularity if non-unit.
171*
172 IF( nounit ) THEN
173 DO 10 info = 1, n
174 IF( a( info, info ).EQ.zero )
175 $ RETURN
176 10 CONTINUE
177 info = 0
178 END IF
179*
180* Determine the block size for this environment.
181*
182 nb = ilaenv( 1, 'CTRTRI', uplo // diag, n, -1, -1, -1 )
183 IF( nb.LE.1 .OR. nb.GE.n ) THEN
184*
185* Use unblocked code
186*
187 CALL ctrti2( uplo, diag, n, a, lda, info )
188 ELSE
189*
190* Use blocked code
191*
192 IF( upper ) THEN
193*
194* Compute inverse of upper triangular matrix
195*
196 DO 20 j = 1, n, nb
197 jb = min( nb, n-j+1 )
198*
199* Compute rows 1:j-1 of current block column
200*
201 CALL ctrmm( 'Left', 'Upper', 'No transpose', diag, j-1,
202 $ jb, one, a, lda, a( 1, j ), lda )
203 CALL ctrsm( 'Right', 'Upper', 'No transpose', diag, j-1,
204 $ jb, -one, a( j, j ), lda, a( 1, j ), lda )
205*
206* Compute inverse of current diagonal block
207*
208 CALL ctrti2( 'Upper', diag, jb, a( j, j ), lda, info )
209 20 CONTINUE
210 ELSE
211*
212* Compute inverse of lower triangular matrix
213*
214 nn = ( ( n-1 ) / nb )*nb + 1
215 DO 30 j = nn, 1, -nb
216 jb = min( nb, n-j+1 )
217 IF( j+jb.LE.n ) THEN
218*
219* Compute rows j+jb:n of current block column
220*
221 CALL ctrmm( 'Left', 'Lower', 'No transpose', diag,
222 $ n-j-jb+1, jb, one, a( j+jb, j+jb ), lda,
223 $ a( j+jb, j ), lda )
224 CALL ctrsm( 'Right', 'Lower', 'No transpose', diag,
225 $ n-j-jb+1, jb, -one, a( j, j ), lda,
226 $ a( j+jb, j ), lda )
227 END IF
228*
229* Compute inverse of current diagonal block
230*
231 CALL ctrti2( 'Lower', diag, jb, a( j, j ), lda, info )
232 30 CONTINUE
233 END IF
234 END IF
235*
236 RETURN
237*
238* End of CTRTRI
239*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:162
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine ctrmm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
CTRMM
Definition ctrmm.f:177
subroutine ctrsm(side, uplo, transa, diag, m, n, alpha, a, lda, b, ldb)
CTRSM
Definition ctrsm.f:180
subroutine ctrti2(uplo, diag, n, a, lda, info)
CTRTI2 computes the inverse of a triangular matrix (unblocked algorithm).
Definition ctrti2.f:110
Here is the call graph for this function:
Here is the caller graph for this function: