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

◆ ctrti2()

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

CTRTI2 computes the inverse of a triangular matrix (unblocked algorithm).

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

Purpose:
!>
!> CTRTI2 computes the inverse of a complex upper or lower triangular
!> matrix.
!>
!> This is the Level 2 BLAS version of the algorithm.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          Specifies whether the matrix A is upper or lower triangular.
!>          = 'U':  Upper triangular
!>          = 'L':  Lower triangular
!> 
[in]DIAG
!>          DIAG is CHARACTER*1
!>          Specifies whether or not the matrix A is unit triangular.
!>          = 'N':  Non-unit triangular
!>          = 'U':  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 = -k, the k-th argument had an illegal value
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.

Definition at line 107 of file ctrti2.f.

108*
109* -- LAPACK computational routine --
110* -- LAPACK is a software package provided by Univ. of Tennessee, --
111* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
112*
113* .. Scalar Arguments ..
114 CHARACTER DIAG, UPLO
115 INTEGER INFO, LDA, N
116* ..
117* .. Array Arguments ..
118 COMPLEX A( LDA, * )
119* ..
120*
121* =====================================================================
122*
123* .. Parameters ..
124 COMPLEX ONE
125 parameter( one = ( 1.0e+0, 0.0e+0 ) )
126* ..
127* .. Local Scalars ..
128 LOGICAL NOUNIT, UPPER
129 INTEGER J
130 COMPLEX AJJ
131* ..
132* .. External Functions ..
133 LOGICAL LSAME
134 EXTERNAL lsame
135* ..
136* .. External Subroutines ..
137 EXTERNAL cscal, ctrmv, xerbla
138* ..
139* .. Intrinsic Functions ..
140 INTRINSIC max
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( 'CTRTI2', -info )
160 RETURN
161 END IF
162*
163 IF( upper ) THEN
164*
165* Compute inverse of upper triangular matrix.
166*
167 DO 10 j = 1, n
168 IF( nounit ) THEN
169 a( j, j ) = one / a( j, j )
170 ajj = -a( j, j )
171 ELSE
172 ajj = -one
173 END IF
174*
175* Compute elements 1:j-1 of j-th column.
176*
177 CALL ctrmv( 'Upper', 'No transpose', diag, j-1, a, lda,
178 $ a( 1, j ), 1 )
179 CALL cscal( j-1, ajj, a( 1, j ), 1 )
180 10 CONTINUE
181 ELSE
182*
183* Compute inverse of lower triangular matrix.
184*
185 DO 20 j = n, 1, -1
186 IF( nounit ) THEN
187 a( j, j ) = one / a( j, j )
188 ajj = -a( j, j )
189 ELSE
190 ajj = -one
191 END IF
192 IF( j.LT.n ) THEN
193*
194* Compute elements j+1:n of j-th column.
195*
196 CALL ctrmv( 'Lower', 'No transpose', diag, n-j,
197 $ a( j+1, j+1 ), lda, a( j+1, j ), 1 )
198 CALL cscal( n-j, ajj, a( j+1, j ), 1 )
199 END IF
200 20 CONTINUE
201 END IF
202*
203 RETURN
204*
205* End of CTRTI2
206*
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 ctrmv(uplo, trans, diag, n, a, lda, x, incx)
CTRMV
Definition ctrmv.f:147
Here is the call graph for this function:
Here is the caller graph for this function: