LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
dsytri_3.f
Go to the documentation of this file.
1*> \brief \b DSYTRI_3
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download DSYTRI_3 + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/dsytri_3.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/dsytri_3.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/dsytri_3.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE DSYTRI_3( UPLO, N, A, LDA, E, IPIV, WORK, LWORK,
20* INFO )
21*
22* .. Scalar Arguments ..
23* CHARACTER UPLO
24* INTEGER INFO, LDA, LWORK, N
25* ..
26* .. Array Arguments ..
27* INTEGER IPIV( * )
28* DOUBLE PRECISION A( LDA, * ), E( * ), WORK( * )
29* ..
30*
31*
32*> \par Purpose:
33* =============
34*>
35*> \verbatim
36*> DSYTRI_3 computes the inverse of a real symmetric indefinite
37*> matrix A using the factorization computed by DSYTRF_RK or DSYTRF_BK:
38*>
39*> A = P*U*D*(U**T)*(P**T) or A = P*L*D*(L**T)*(P**T),
40*>
41*> where U (or L) is unit upper (or lower) triangular matrix,
42*> U**T (or L**T) is the transpose of U (or L), P is a permutation
43*> matrix, P**T is the transpose of P, and D is symmetric and block
44*> diagonal with 1-by-1 and 2-by-2 diagonal blocks.
45*>
46*> DSYTRI_3 sets the leading dimension of the workspace before calling
47*> DSYTRI_3X that actually computes the inverse. This is the blocked
48*> version of the algorithm, calling Level 3 BLAS.
49*> \endverbatim
50*
51* Arguments:
52* ==========
53*
54*> \param[in] UPLO
55*> \verbatim
56*> UPLO is CHARACTER*1
57*> Specifies whether the details of the factorization are
58*> stored as an upper or lower triangular matrix.
59*> = 'U': Upper triangle of A is stored;
60*> = 'L': Lower triangle of A is stored.
61*> \endverbatim
62*>
63*> \param[in] N
64*> \verbatim
65*> N is INTEGER
66*> The order of the matrix A. N >= 0.
67*> \endverbatim
68*>
69*> \param[in,out] A
70*> \verbatim
71*> A is DOUBLE PRECISION array, dimension (LDA,N)
72*> On entry, diagonal of the block diagonal matrix D and
73*> factors U or L as computed by DSYTRF_RK and DSYTRF_BK:
74*> a) ONLY diagonal elements of the symmetric block diagonal
75*> matrix D on the diagonal of A, i.e. D(k,k) = A(k,k);
76*> (superdiagonal (or subdiagonal) elements of D
77*> should be provided on entry in array E), and
78*> b) If UPLO = 'U': factor U in the superdiagonal part of A.
79*> If UPLO = 'L': factor L in the subdiagonal part of A.
80*>
81*> On exit, if INFO = 0, the symmetric inverse of the original
82*> matrix.
83*> If UPLO = 'U': the upper triangular part of the inverse
84*> is formed and the part of A below the diagonal is not
85*> referenced;
86*> If UPLO = 'L': the lower triangular part of the inverse
87*> is formed and the part of A above the diagonal is not
88*> referenced.
89*> \endverbatim
90*>
91*> \param[in] LDA
92*> \verbatim
93*> LDA is INTEGER
94*> The leading dimension of the array A. LDA >= max(1,N).
95*> \endverbatim
96*>
97*> \param[in] E
98*> \verbatim
99*> E is DOUBLE PRECISION array, dimension (N)
100*> On entry, contains the superdiagonal (or subdiagonal)
101*> elements of the symmetric block diagonal matrix D
102*> with 1-by-1 or 2-by-2 diagonal blocks, where
103*> If UPLO = 'U': E(i) = D(i-1,i),i=2:N, E(1) not referenced;
104*> If UPLO = 'L': E(i) = D(i+1,i),i=1:N-1, E(N) not referenced.
105*>
106*> NOTE: For 1-by-1 diagonal block D(k), where
107*> 1 <= k <= N, the element E(k) is not referenced in both
108*> UPLO = 'U' or UPLO = 'L' cases.
109*> \endverbatim
110*>
111*> \param[in] IPIV
112*> \verbatim
113*> IPIV is INTEGER array, dimension (N)
114*> Details of the interchanges and the block structure of D
115*> as determined by DSYTRF_RK or DSYTRF_BK.
116*> \endverbatim
117*>
118*> \param[out] WORK
119*> \verbatim
120*> WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK)).
121*> On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
122*> \endverbatim
123*>
124*> \param[in] LWORK
125*> \verbatim
126*> LWORK is INTEGER
127*> The length of WORK.
128*> If N = 0, LWORK >= 1, else LWORK >= (N+NB+1)*(NB+3).
129*>
130*> If LWORK = -1, then a workspace query is assumed;
131*> the routine only calculates the optimal size of the optimal
132*> size of the WORK array, returns this value as the first
133*> entry of the WORK array, and no error message related to
134*> LWORK is issued by XERBLA.
135*> \endverbatim
136*>
137*> \param[out] INFO
138*> \verbatim
139*> INFO is INTEGER
140*> = 0: successful exit
141*> < 0: if INFO = -i, the i-th argument had an illegal value
142*> > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
143*> inverse could not be computed.
144*> \endverbatim
145*
146* Authors:
147* ========
148*
149*> \author Univ. of Tennessee
150*> \author Univ. of California Berkeley
151*> \author Univ. of Colorado Denver
152*> \author NAG Ltd.
153*
154*> \ingroup hetri_3
155*
156*> \par Contributors:
157* ==================
158*> \verbatim
159*>
160*> November 2017, Igor Kozachenko,
161*> Computer Science Division,
162*> University of California, Berkeley
163*>
164*> \endverbatim
165*
166* =====================================================================
167 SUBROUTINE dsytri_3( UPLO, N, A, LDA, E, IPIV, WORK, LWORK,
168 $ INFO )
169*
170* -- LAPACK computational routine --
171* -- LAPACK is a software package provided by Univ. of Tennessee, --
172* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
173*
174* .. Scalar Arguments ..
175 CHARACTER UPLO
176 INTEGER INFO, LDA, LWORK, N
177* ..
178* .. Array Arguments ..
179 INTEGER IPIV( * )
180 DOUBLE PRECISION A( LDA, * ), E( * ), WORK( * )
181* ..
182*
183* =====================================================================
184*
185* .. Local Scalars ..
186 LOGICAL UPPER, LQUERY
187 INTEGER LWKOPT, NB
188* ..
189* .. External Functions ..
190 LOGICAL LSAME
191 INTEGER ILAENV
192 EXTERNAL lsame, ilaenv
193* ..
194* .. External Subroutines ..
195 EXTERNAL dsytri_3x, xerbla
196* ..
197* .. Intrinsic Functions ..
198 INTRINSIC max
199* ..
200* .. Executable Statements ..
201*
202* Test the input parameters.
203*
204 info = 0
205 upper = lsame( uplo, 'U' )
206 lquery = ( lwork.EQ.-1 )
207*
208* Determine the block size
209*
210 IF( n.EQ.0 ) THEN
211 lwkopt = 1
212 ELSE
213 nb = max( 1, ilaenv( 1, 'DSYTRI_3', uplo, n, -1, -1, -1 ) )
214 lwkopt = ( n+nb+1 ) * ( nb+3 )
215 END IF
216 work( 1 ) = lwkopt
217*
218 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
219 info = -1
220 ELSE IF( n.LT.0 ) THEN
221 info = -2
222 ELSE IF( lda.LT.max( 1, n ) ) THEN
223 info = -4
224 ELSE IF( lwork.LT.lwkopt .AND. .NOT.lquery ) THEN
225 info = -8
226 END IF
227*
228 IF( info.NE.0 ) THEN
229 CALL xerbla( 'DSYTRI_3', -info )
230 RETURN
231 ELSE IF( lquery ) THEN
232 RETURN
233 END IF
234*
235* Quick return if possible
236*
237 IF( n.EQ.0 )
238 $ RETURN
239*
240 CALL dsytri_3x( uplo, n, a, lda, e, ipiv, work, nb, info )
241*
242 work( 1 ) = lwkopt
243*
244 RETURN
245*
246* End of DSYTRI_3
247*
248 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dsytri_3(uplo, n, a, lda, e, ipiv, work, lwork, info)
DSYTRI_3
Definition dsytri_3.f:169
subroutine dsytri_3x(uplo, n, a, lda, e, ipiv, work, nb, info)
DSYTRI_3X
Definition dsytri_3x.f:158