LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
strti2.f
Go to the documentation of this file.
1*> \brief \b STRTI2 computes the inverse of a triangular matrix (unblocked algorithm).
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download STRTI2 + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/strti2.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/strti2.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/strti2.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE STRTI2( UPLO, DIAG, N, A, LDA, INFO )
22*
23* .. Scalar Arguments ..
24* CHARACTER DIAG, UPLO
25* INTEGER INFO, LDA, N
26* ..
27* .. Array Arguments ..
28* REAL A( LDA, * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*>
37*> STRTI2 computes the inverse of a real upper or lower triangular
38*> matrix.
39*>
40*> This is the Level 2 BLAS version of the algorithm.
41*> \endverbatim
42*
43* Arguments:
44* ==========
45*
46*> \param[in] UPLO
47*> \verbatim
48*> UPLO is CHARACTER*1
49*> Specifies whether the matrix A is upper or lower triangular.
50*> = 'U': Upper triangular
51*> = 'L': Lower triangular
52*> \endverbatim
53*>
54*> \param[in] DIAG
55*> \verbatim
56*> DIAG is CHARACTER*1
57*> Specifies whether or not the matrix A is unit triangular.
58*> = 'N': Non-unit triangular
59*> = 'U': Unit triangular
60*> \endverbatim
61*>
62*> \param[in] N
63*> \verbatim
64*> N is INTEGER
65*> The order of the matrix A. N >= 0.
66*> \endverbatim
67*>
68*> \param[in,out] A
69*> \verbatim
70*> A is REAL array, dimension (LDA,N)
71*> On entry, the triangular matrix A. If UPLO = 'U', the
72*> leading n by n upper triangular part of the array A contains
73*> the upper triangular matrix, and the strictly lower
74*> triangular part of A is not referenced. If UPLO = 'L', the
75*> leading n by n lower triangular part of the array A contains
76*> the lower triangular matrix, and the strictly upper
77*> triangular part of A is not referenced. If DIAG = 'U', the
78*> diagonal elements of A are also not referenced and are
79*> assumed to be 1.
80*>
81*> On exit, the (triangular) inverse of the original matrix, in
82*> the same storage format.
83*> \endverbatim
84*>
85*> \param[in] LDA
86*> \verbatim
87*> LDA is INTEGER
88*> The leading dimension of the array A. LDA >= max(1,N).
89*> \endverbatim
90*>
91*> \param[out] INFO
92*> \verbatim
93*> INFO is INTEGER
94*> = 0: successful exit
95*> < 0: if INFO = -k, the k-th argument had an illegal value
96*> \endverbatim
97*
98* Authors:
99* ========
100*
101*> \author Univ. of Tennessee
102*> \author Univ. of California Berkeley
103*> \author Univ. of Colorado Denver
104*> \author NAG Ltd.
105*
106*> \ingroup trti2
107*
108* =====================================================================
109 SUBROUTINE strti2( UPLO, DIAG, N, A, LDA, INFO )
110*
111* -- LAPACK computational routine --
112* -- LAPACK is a software package provided by Univ. of Tennessee, --
113* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
114*
115* .. Scalar Arguments ..
116 CHARACTER DIAG, UPLO
117 INTEGER INFO, LDA, N
118* ..
119* .. Array Arguments ..
120 REAL A( LDA, * )
121* ..
122*
123* =====================================================================
124*
125* .. Parameters ..
126 REAL ONE
127 parameter( one = 1.0e+0 )
128* ..
129* .. Local Scalars ..
130 LOGICAL NOUNIT, UPPER
131 INTEGER J
132 REAL AJJ
133* ..
134* .. External Functions ..
135 LOGICAL LSAME
136 EXTERNAL lsame
137* ..
138* .. External Subroutines ..
139 EXTERNAL sscal, strmv, xerbla
140* ..
141* .. Intrinsic Functions ..
142 INTRINSIC max
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( 'STRTI2', -info )
162 RETURN
163 END IF
164*
165 IF( upper ) THEN
166*
167* Compute inverse of upper triangular matrix.
168*
169 DO 10 j = 1, n
170 IF( nounit ) THEN
171 a( j, j ) = one / a( j, j )
172 ajj = -a( j, j )
173 ELSE
174 ajj = -one
175 END IF
176*
177* Compute elements 1:j-1 of j-th column.
178*
179 CALL strmv( 'Upper', 'No transpose', diag, j-1, a, lda,
180 $ a( 1, j ), 1 )
181 CALL sscal( j-1, ajj, a( 1, j ), 1 )
182 10 CONTINUE
183 ELSE
184*
185* Compute inverse of lower triangular matrix.
186*
187 DO 20 j = n, 1, -1
188 IF( nounit ) THEN
189 a( j, j ) = one / a( j, j )
190 ajj = -a( j, j )
191 ELSE
192 ajj = -one
193 END IF
194 IF( j.LT.n ) THEN
195*
196* Compute elements j+1:n of j-th column.
197*
198 CALL strmv( 'Lower', 'No transpose', diag, n-j,
199 $ a( j+1, j+1 ), lda, a( j+1, j ), 1 )
200 CALL sscal( n-j, ajj, a( j+1, j ), 1 )
201 END IF
202 20 CONTINUE
203 END IF
204*
205 RETURN
206*
207* End of STRTI2
208*
209 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
subroutine strmv(uplo, trans, diag, n, a, lda, x, incx)
STRMV
Definition strmv.f:147
subroutine strti2(uplo, diag, n, a, lda, info)
STRTI2 computes the inverse of a triangular matrix (unblocked algorithm).
Definition strti2.f:110