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

◆ stptri()

subroutine stptri ( character uplo,
character diag,
integer n,
real, dimension( * ) ap,
integer info )

STPTRI

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

Purpose:
!>
!> STPTRI computes the inverse of a real upper or lower triangular
!> matrix A stored in packed format.
!> 
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]AP
!>          AP is REAL array, dimension (N*(N+1)/2)
!>          On entry, the upper or lower triangular matrix A, stored
!>          columnwise in a linear array.  The j-th column of A is stored
!>          in the array AP as follows:
!>          if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
!>          if UPLO = 'L', AP(i + (j-1)*((2*n-j)/2) = A(i,j) for j<=i<=n.
!>          See below for further details.
!>          On exit, the (triangular) inverse of the original matrix, in
!>          the same packed storage format.
!> 
[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.
Further Details:
!>
!>  A triangular matrix A can be transferred to packed storage using one
!>  of the following program segments:
!>
!>  UPLO = 'U':                      UPLO = 'L':
!>
!>        JC = 1                           JC = 1
!>        DO 2 J = 1, N                    DO 2 J = 1, N
!>           DO 1 I = 1, J                    DO 1 I = J, N
!>              AP(JC+I-1) = A(I,J)              AP(JC+I-J) = A(I,J)
!>      1    CONTINUE                    1    CONTINUE
!>           JC = JC + J                      JC = JC + N - J + 1
!>      2 CONTINUE                       2 CONTINUE
!> 

Definition at line 114 of file stptri.f.

115*
116* -- LAPACK computational routine --
117* -- LAPACK is a software package provided by Univ. of Tennessee, --
118* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
119*
120* .. Scalar Arguments ..
121 CHARACTER DIAG, UPLO
122 INTEGER INFO, N
123* ..
124* .. Array Arguments ..
125 REAL AP( * )
126* ..
127*
128* =====================================================================
129*
130* .. Parameters ..
131 REAL ONE, ZERO
132 parameter( one = 1.0e+0, zero = 0.0e+0 )
133* ..
134* .. Local Scalars ..
135 LOGICAL NOUNIT, UPPER
136 INTEGER J, JC, JCLAST, JJ
137 REAL AJJ
138* ..
139* .. External Functions ..
140 LOGICAL LSAME
141 EXTERNAL lsame
142* ..
143* .. External Subroutines ..
144 EXTERNAL sscal, stpmv, xerbla
145* ..
146* .. Executable Statements ..
147*
148* Test the input parameters.
149*
150 info = 0
151 upper = lsame( uplo, 'U' )
152 nounit = lsame( diag, 'N' )
153 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
154 info = -1
155 ELSE IF( .NOT.nounit .AND. .NOT.lsame( diag, 'U' ) ) THEN
156 info = -2
157 ELSE IF( n.LT.0 ) THEN
158 info = -3
159 END IF
160 IF( info.NE.0 ) THEN
161 CALL xerbla( 'STPTRI', -info )
162 RETURN
163 END IF
164*
165* Check for singularity if non-unit.
166*
167 IF( nounit ) THEN
168 IF( upper ) THEN
169 jj = 0
170 DO 10 info = 1, n
171 jj = jj + info
172 IF( ap( jj ).EQ.zero )
173 $ RETURN
174 10 CONTINUE
175 ELSE
176 jj = 1
177 DO 20 info = 1, n
178 IF( ap( jj ).EQ.zero )
179 $ RETURN
180 jj = jj + n - info + 1
181 20 CONTINUE
182 END IF
183 info = 0
184 END IF
185*
186 IF( upper ) THEN
187*
188* Compute inverse of upper triangular matrix.
189*
190 jc = 1
191 DO 30 j = 1, n
192 IF( nounit ) THEN
193 ap( jc+j-1 ) = one / ap( jc+j-1 )
194 ajj = -ap( jc+j-1 )
195 ELSE
196 ajj = -one
197 END IF
198*
199* Compute elements 1:j-1 of j-th column.
200*
201 CALL stpmv( 'Upper', 'No transpose', diag, j-1, ap,
202 $ ap( jc ), 1 )
203 CALL sscal( j-1, ajj, ap( jc ), 1 )
204 jc = jc + j
205 30 CONTINUE
206*
207 ELSE
208*
209* Compute inverse of lower triangular matrix.
210*
211 jc = n*( n+1 ) / 2
212 DO 40 j = n, 1, -1
213 IF( nounit ) THEN
214 ap( jc ) = one / ap( jc )
215 ajj = -ap( jc )
216 ELSE
217 ajj = -one
218 END IF
219 IF( j.LT.n ) THEN
220*
221* Compute elements j+1:n of j-th column.
222*
223 CALL stpmv( 'Lower', 'No transpose', diag, n-j,
224 $ ap( jclast ), ap( jc+1 ), 1 )
225 CALL sscal( n-j, ajj, ap( jc+1 ), 1 )
226 END IF
227 jclast = jc
228 jc = jc - n + j - 2
229 40 CONTINUE
230 END IF
231*
232 RETURN
233*
234* End of STPTRI
235*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
subroutine sscal(n, sa, sx, incx)
SSCAL
Definition sscal.f:79
subroutine stpmv(uplo, trans, diag, n, ap, x, incx)
STPMV
Definition stpmv.f:142
Here is the call graph for this function:
Here is the caller graph for this function: