LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ctrtri.f
Go to the documentation of this file.
1*> \brief \b CTRTRI
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CTRTRI + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ctrtri.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ctrtri.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ctrtri.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CTRTRI( UPLO, DIAG, N, A, LDA, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER DIAG, UPLO
23* INTEGER INFO, LDA, N
24* ..
25* .. Array Arguments ..
26* COMPLEX A( LDA, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CTRTRI computes the inverse of a complex upper or lower triangular
36*> matrix A.
37*>
38*> This is the Level 3 BLAS version of the algorithm.
39*> \endverbatim
40*
41* Arguments:
42* ==========
43*
44*> \param[in] UPLO
45*> \verbatim
46*> UPLO is CHARACTER*1
47*> = 'U': A is upper triangular;
48*> = 'L': A is lower triangular.
49*> \endverbatim
50*>
51*> \param[in] DIAG
52*> \verbatim
53*> DIAG is CHARACTER*1
54*> = 'N': A is non-unit triangular;
55*> = 'U': A is unit triangular.
56*> \endverbatim
57*>
58*> \param[in] N
59*> \verbatim
60*> N is INTEGER
61*> The order of the matrix A. N >= 0.
62*> \endverbatim
63*>
64*> \param[in,out] A
65*> \verbatim
66*> A is COMPLEX array, dimension (LDA,N)
67*> On entry, the triangular matrix A. If UPLO = 'U', the
68*> leading N-by-N upper triangular part of the array A contains
69*> the upper triangular matrix, and the strictly lower
70*> triangular part of A is not referenced. If UPLO = 'L', the
71*> leading N-by-N lower triangular part of the array A contains
72*> the lower triangular matrix, and the strictly upper
73*> triangular part of A is not referenced. If DIAG = 'U', the
74*> diagonal elements of A are also not referenced and are
75*> assumed to be 1.
76*> On exit, the (triangular) inverse of the original matrix, in
77*> the same storage format.
78*> \endverbatim
79*>
80*> \param[in] LDA
81*> \verbatim
82*> LDA is INTEGER
83*> The leading dimension of the array A. LDA >= max(1,N).
84*> \endverbatim
85*>
86*> \param[out] INFO
87*> \verbatim
88*> INFO is INTEGER
89*> = 0: successful exit
90*> < 0: if INFO = -i, the i-th argument had an illegal value
91*> > 0: if INFO = i, A(i,i) is exactly zero. The triangular
92*> matrix is singular and its inverse can not be computed.
93*> \endverbatim
94*
95* Authors:
96* ========
97*
98*> \author Univ. of Tennessee
99*> \author Univ. of California Berkeley
100*> \author Univ. of Colorado Denver
101*> \author NAG Ltd.
102*
103*> \ingroup trtri
104*
105* =====================================================================
106 SUBROUTINE ctrtri( UPLO, DIAG, N, A, LDA, INFO )
107*
108* -- LAPACK computational routine --
109* -- LAPACK is a software package provided by Univ. of Tennessee, --
110* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
111*
112* .. Scalar Arguments ..
113 CHARACTER DIAG, UPLO
114 INTEGER INFO, LDA, N
115* ..
116* .. Array Arguments ..
117 COMPLEX A( LDA, * )
118* ..
119*
120* =====================================================================
121*
122* .. Parameters ..
123 COMPLEX ONE, ZERO
124 parameter( one = ( 1.0e+0, 0.0e+0 ),
125 $ zero = ( 0.0e+0, 0.0e+0 ) )
126* ..
127* .. Local Scalars ..
128 LOGICAL NOUNIT, UPPER
129 INTEGER J, JB, NB, NN
130* ..
131* .. External Functions ..
132 LOGICAL LSAME
133 INTEGER ILAENV
134 EXTERNAL lsame, ilaenv
135* ..
136* .. External Subroutines ..
137 EXTERNAL ctrmm, ctrsm, ctrti2, xerbla
138* ..
139* .. Intrinsic Functions ..
140 INTRINSIC max, min
141* ..
142* .. Executable Statements ..
143*
144* Test the input parameters.
145*
146 info = 0
147 upper = lsame( uplo, 'U' )
148 nounit = lsame( diag, 'N' )
149 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
150 info = -1
151 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
152 info = -2
153 ELSE IF( n.LT.0 ) THEN
154 info = -3
155 ELSE IF( lda.LT.max( 1, n ) ) THEN
156 info = -5
157 END IF
158 IF( info.NE.0 ) THEN
159 CALL xerbla( 'CTRTRI', -info )
160 RETURN
161 END IF
162*
163* Quick return if possible
164*
165 IF( n.EQ.0 )
166 $ RETURN
167*
168* Check for singularity if non-unit.
169*
170 IF( nounit ) THEN
171 DO 10 info = 1, n
172 IF( a( info, info ).EQ.zero )
173 $ RETURN
174 10 CONTINUE
175 info = 0
176 END IF
177*
178* Determine the block size for this environment.
179*
180 nb = ilaenv( 1, 'CTRTRI', uplo // diag, n, -1, -1, -1 )
181 IF( nb.LE.1 .OR. nb.GE.n ) THEN
182*
183* Use unblocked code
184*
185 CALL ctrti2( uplo, diag, n, a, lda, info )
186 ELSE
187*
188* Use blocked code
189*
190 IF( upper ) THEN
191*
192* Compute inverse of upper triangular matrix
193*
194 DO 20 j = 1, n, nb
195 jb = min( nb, n-j+1 )
196*
197* Compute rows 1:j-1 of current block column
198*
199 CALL ctrmm( 'Left', 'Upper', 'No transpose', diag,
200 $ j-1,
201 $ jb, one, a, lda, a( 1, j ), lda )
202 CALL ctrsm( 'Right', 'Upper', 'No transpose', diag,
203 $ 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*
240 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
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:108
subroutine ctrtri(uplo, diag, n, a, lda, info)
CTRTRI
Definition ctrtri.f:107