LAPACK 3.12.1
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*> Download STRTI2 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/strti2.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/strti2.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/strti2.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE STRTI2( UPLO, DIAG, N, A, LDA, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER DIAG, UPLO
23* INTEGER INFO, LDA, N
24* ..
25* .. Array Arguments ..
26* REAL A( LDA, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> STRTI2 computes the inverse of a real upper or lower triangular
36*> matrix.
37*>
38*> This is the Level 2 BLAS version of the algorithm.
39*> \endverbatim
40*
41* Arguments:
42* ==========
43*
44*> \param[in] UPLO
45*> \verbatim
46*> UPLO is CHARACTER*1
47*> Specifies whether the matrix A is upper or lower triangular.
48*> = 'U': Upper triangular
49*> = 'L': Lower triangular
50*> \endverbatim
51*>
52*> \param[in] DIAG
53*> \verbatim
54*> DIAG is CHARACTER*1
55*> Specifies whether or not the matrix A is unit triangular.
56*> = 'N': Non-unit triangular
57*> = 'U': Unit triangular
58*> \endverbatim
59*>
60*> \param[in] N
61*> \verbatim
62*> N is INTEGER
63*> The order of the matrix A. N >= 0.
64*> \endverbatim
65*>
66*> \param[in,out] A
67*> \verbatim
68*> A is REAL array, dimension (LDA,N)
69*> On entry, the triangular matrix A. If UPLO = 'U', the
70*> leading n by n upper triangular part of the array A contains
71*> the upper triangular matrix, and the strictly lower
72*> triangular part of A is not referenced. If UPLO = 'L', the
73*> leading n by n lower triangular part of the array A contains
74*> the lower triangular matrix, and the strictly upper
75*> triangular part of A is not referenced. If DIAG = 'U', the
76*> diagonal elements of A are also not referenced and are
77*> assumed to be 1.
78*>
79*> On exit, the (triangular) inverse of the original matrix, in
80*> the same storage format.
81*> \endverbatim
82*>
83*> \param[in] LDA
84*> \verbatim
85*> LDA is INTEGER
86*> The leading dimension of the array A. LDA >= max(1,N).
87*> \endverbatim
88*>
89*> \param[out] INFO
90*> \verbatim
91*> INFO is INTEGER
92*> = 0: successful exit
93*> < 0: if INFO = -k, the k-th argument had an illegal value
94*> \endverbatim
95*
96* Authors:
97* ========
98*
99*> \author Univ. of Tennessee
100*> \author Univ. of California Berkeley
101*> \author Univ. of Colorado Denver
102*> \author NAG Ltd.
103*
104*> \ingroup trti2
105*
106* =====================================================================
107 SUBROUTINE strti2( UPLO, DIAG, N, A, LDA, INFO )
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 REAL A( LDA, * )
119* ..
120*
121* =====================================================================
122*
123* .. Parameters ..
124 REAL ONE
125 parameter( one = 1.0e+0 )
126* ..
127* .. Local Scalars ..
128 LOGICAL NOUNIT, UPPER
129 INTEGER J
130 REAL AJJ
131* ..
132* .. External Functions ..
133 LOGICAL LSAME
134 EXTERNAL lsame
135* ..
136* .. External Subroutines ..
137 EXTERNAL sscal, strmv, 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( 'STRTI2', -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 strmv( 'Upper', 'No transpose', diag, j-1, a, lda,
178 $ a( 1, j ), 1 )
179 CALL sscal( 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 strmv( 'Lower', 'No transpose', diag, n-j,
197 $ a( j+1, j+1 ), lda, a( j+1, j ), 1 )
198 CALL sscal( n-j, ajj, a( j+1, j ), 1 )
199 END IF
200 20 CONTINUE
201 END IF
202*
203 RETURN
204*
205* End of STRTI2
206*
207 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:108