LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dtptri.f
Go to the documentation of this file.
1*> \brief \b DTPTRI
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DTPTRI + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dtptri.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dtptri.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dtptri.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DTPTRI( UPLO, DIAG, N, AP, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER DIAG, UPLO
23* INTEGER INFO, N
24* ..
25* .. Array Arguments ..
26* DOUBLE PRECISION AP( * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> DTPTRI computes the inverse of a real upper or lower triangular
36*> matrix A stored in packed format.
37*> \endverbatim
38*
39* Arguments:
40* ==========
41*
42*> \param[in] UPLO
43*> \verbatim
44*> UPLO is CHARACTER*1
45*> = 'U': A is upper triangular;
46*> = 'L': A is lower triangular.
47*> \endverbatim
48*>
49*> \param[in] DIAG
50*> \verbatim
51*> DIAG is CHARACTER*1
52*> = 'N': A is non-unit triangular;
53*> = 'U': A is unit triangular.
54*> \endverbatim
55*>
56*> \param[in] N
57*> \verbatim
58*> N is INTEGER
59*> The order of the matrix A. N >= 0.
60*> \endverbatim
61*>
62*> \param[in,out] AP
63*> \verbatim
64*> AP is DOUBLE PRECISION array, dimension (N*(N+1)/2)
65*> On entry, the upper or lower triangular matrix A, stored
66*> columnwise in a linear array. The j-th column of A is stored
67*> in the array AP as follows:
68*> if UPLO = 'U', AP(i + (j-1)*j/2) = A(i,j) for 1<=i<=j;
69*> if UPLO = 'L', AP(i + (j-1)*((2*n-j)/2) = A(i,j) for j<=i<=n.
70*> See below for further details.
71*> On exit, the (triangular) inverse of the original matrix, in
72*> the same packed storage format.
73*> \endverbatim
74*>
75*> \param[out] INFO
76*> \verbatim
77*> INFO is INTEGER
78*> = 0: successful exit
79*> < 0: if INFO = -i, the i-th argument had an illegal value
80*> > 0: if INFO = i, A(i,i) is exactly zero. The triangular
81*> matrix is singular and its inverse can not be computed.
82*> \endverbatim
83*
84* Authors:
85* ========
86*
87*> \author Univ. of Tennessee
88*> \author Univ. of California Berkeley
89*> \author Univ. of Colorado Denver
90*> \author NAG Ltd.
91*
92*> \ingroup tptri
93*
94*> \par Further Details:
95* =====================
96*>
97*> \verbatim
98*>
99*> A triangular matrix A can be transferred to packed storage using one
100*> of the following program segments:
101*>
102*> UPLO = 'U': UPLO = 'L':
103*>
104*> JC = 1 JC = 1
105*> DO 2 J = 1, N DO 2 J = 1, N
106*> DO 1 I = 1, J DO 1 I = J, N
107*> AP(JC+I-1) = A(I,J) AP(JC+I-J) = A(I,J)
108*> 1 CONTINUE 1 CONTINUE
109*> JC = JC + J JC = JC + N - J + 1
110*> 2 CONTINUE 2 CONTINUE
111*> \endverbatim
112*>
113* =====================================================================
114 SUBROUTINE dtptri( UPLO, DIAG, N, AP, INFO )
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 DOUBLE PRECISION AP( * )
126* ..
127*
128* =====================================================================
129*
130* .. Parameters ..
131 DOUBLE PRECISION ONE, ZERO
132 parameter( one = 1.0d+0, zero = 0.0d+0 )
133* ..
134* .. Local Scalars ..
135 LOGICAL NOUNIT, UPPER
136 INTEGER J, JC, JCLAST, JJ
137 DOUBLE PRECISION AJJ
138* ..
139* .. External Functions ..
140 LOGICAL LSAME
141 EXTERNAL lsame
142* ..
143* .. External Subroutines ..
144 EXTERNAL dscal, dtpmv, 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( 'DTPTRI', -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 dtpmv( 'Upper', 'No transpose', diag, j-1, ap,
202 $ ap( jc ), 1 )
203 CALL dscal( 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 dtpmv( 'Lower', 'No transpose', diag, n-j,
224 $ ap( jclast ), ap( jc+1 ), 1 )
225 CALL dscal( 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 DTPTRI
235*
236 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dscal(n, da, dx, incx)
DSCAL
Definition dscal.f:79
subroutine dtpmv(uplo, trans, diag, n, ap, x, incx)
DTPMV
Definition dtpmv.f:142
subroutine dtptri(uplo, diag, n, ap, info)
DTPTRI
Definition dtptri.f:115