LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
ssytri2.f
Go to the documentation of this file.
1*> \brief \b SSYTRI2
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download SSYTRI2 + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ssytri2.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ssytri2.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ssytri2.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18* Definition:
19* ===========
20*
21* SUBROUTINE SSYTRI2( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
22*
23* .. Scalar Arguments ..
24* CHARACTER UPLO
25* INTEGER INFO, LDA, LWORK, N
26* ..
27* .. Array Arguments ..
28* INTEGER IPIV( * )
29* REAL A( LDA, * ), WORK( * )
30* ..
31*
32*
33*> \par Purpose:
34* =============
35*>
36*> \verbatim
37*>
38*> SSYTRI2 computes the inverse of a REAL symmetric indefinite matrix
39*> A using the factorization A = U*D*U**T or A = L*D*L**T computed by
40*> SSYTRF. SSYTRI2 sets the LEADING DIMENSION of the workspace
41*> before calling SSYTRI2X that actually computes the inverse.
42*> \endverbatim
43*
44* Arguments:
45* ==========
46*
47*> \param[in] UPLO
48*> \verbatim
49*> UPLO is CHARACTER*1
50*> Specifies whether the details of the factorization are stored
51*> as an upper or lower triangular matrix.
52*> = 'U': Upper triangular, form is A = U*D*U**T;
53*> = 'L': Lower triangular, form is A = L*D*L**T.
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] A
63*> \verbatim
64*> A is REAL array, dimension (LDA,N)
65*> On entry, the block diagonal matrix D and the multipliers
66*> used to obtain the factor U or L as computed by SSYTRF.
67*>
68*> On exit, if INFO = 0, the (symmetric) inverse of the original
69*> matrix. If UPLO = 'U', the upper triangular part of the
70*> inverse is formed and the part of A below the diagonal is not
71*> referenced; if UPLO = 'L' the lower triangular part of the
72*> inverse is formed and the part of A above the diagonal is
73*> not referenced.
74*> \endverbatim
75*>
76*> \param[in] LDA
77*> \verbatim
78*> LDA is INTEGER
79*> The leading dimension of the array A. LDA >= max(1,N).
80*> \endverbatim
81*>
82*> \param[in] IPIV
83*> \verbatim
84*> IPIV is INTEGER array, dimension (N)
85*> Details of the interchanges and the block structure of D
86*> as determined by SSYTRF.
87*> \endverbatim
88*>
89*> \param[out] WORK
90*> \verbatim
91*> WORK is REAL array, dimension (N+NB+1)*(NB+3)
92*> \endverbatim
93*>
94*> \param[in] LWORK
95*> \verbatim
96*> LWORK is INTEGER
97*> The dimension of the array WORK.
98*> WORK is size >= (N+NB+1)*(NB+3)
99*> If LWORK = -1, then a workspace query is assumed; the routine
100*> calculates:
101*> - the optimal size of the WORK array, returns
102*> this value as the first entry of the WORK array,
103*> - and no error message related to LWORK is issued by XERBLA.
104*> \endverbatim
105*>
106*> \param[out] INFO
107*> \verbatim
108*> INFO is INTEGER
109*> = 0: successful exit
110*> < 0: if INFO = -i, the i-th argument had an illegal value
111*> > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
112*> inverse could not be computed.
113*> \endverbatim
114*
115* Authors:
116* ========
117*
118*> \author Univ. of Tennessee
119*> \author Univ. of California Berkeley
120*> \author Univ. of Colorado Denver
121*> \author NAG Ltd.
122*
123*> \ingroup hetri2
124*
125* =====================================================================
126 SUBROUTINE ssytri2( UPLO, N, A, LDA, IPIV, WORK, LWORK, INFO )
127*
128* -- LAPACK computational routine --
129* -- LAPACK is a software package provided by Univ. of Tennessee, --
130* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
131*
132* .. Scalar Arguments ..
133 CHARACTER UPLO
134 INTEGER INFO, LDA, LWORK, N
135* ..
136* .. Array Arguments ..
137 INTEGER IPIV( * )
138 REAL A( LDA, * ), WORK( * )
139* ..
140*
141* =====================================================================
142*
143* .. Local Scalars ..
144 LOGICAL UPPER, LQUERY
145 INTEGER MINSIZE, NBMAX
146* ..
147* .. External Functions ..
148 LOGICAL LSAME
149 INTEGER ILAENV
150 EXTERNAL lsame, ilaenv
151* ..
152* .. External Subroutines ..
153 EXTERNAL ssytri, ssytri2x, xerbla
154* ..
155* .. Executable Statements ..
156*
157* Test the input parameters.
158*
159 info = 0
160 upper = lsame( uplo, 'U' )
161 lquery = ( lwork.EQ.-1 )
162* Get blocksize
163 nbmax = ilaenv( 1, 'SSYTRF', uplo, n, -1, -1, -1 )
164 IF ( nbmax .GE. n ) THEN
165 minsize = n
166 ELSE
167 minsize = (n+nbmax+1)*(nbmax+3)
168 END IF
169*
170 IF( .NOT.upper .AND. .NOT.lsame( uplo, 'L' ) ) THEN
171 info = -1
172 ELSE IF( n.LT.0 ) THEN
173 info = -2
174 ELSE IF( lda.LT.max( 1, n ) ) THEN
175 info = -4
176 ELSE IF (lwork .LT. minsize .AND. .NOT.lquery ) THEN
177 info = -7
178 END IF
179*
180* Quick return if possible
181*
182*
183 IF( info.NE.0 ) THEN
184 CALL xerbla( 'SSYTRI2', -info )
185 RETURN
186 ELSE IF( lquery ) THEN
187 work(1)=minsize
188 RETURN
189 END IF
190 IF( n.EQ.0 )
191 $ RETURN
192
193 IF( nbmax .GE. n ) THEN
194 CALL ssytri( uplo, n, a, lda, ipiv, work, info )
195 ELSE
196 CALL ssytri2x( uplo, n, a, lda, ipiv, work, nbmax, info )
197 END IF
198 RETURN
199*
200* End of SSYTRI2
201*
202 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine ssytri2(uplo, n, a, lda, ipiv, work, lwork, info)
SSYTRI2
Definition ssytri2.f:127
subroutine ssytri2x(uplo, n, a, lda, ipiv, work, nb, info)
SSYTRI2X
Definition ssytri2x.f:120
subroutine ssytri(uplo, n, a, lda, ipiv, work, info)
SSYTRI
Definition ssytri.f:114