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