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

◆ dsytri_3()

subroutine dsytri_3 ( character uplo,
integer n,
double precision, dimension( lda, * ) a,
integer lda,
double precision, dimension( * ) e,
integer, dimension( * ) ipiv,
double precision, dimension( * ) work,
integer lwork,
integer info )

DSYTRI_3

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

Purpose:
!> DSYTRI_3 computes the inverse of a real symmetric indefinite
!> matrix A using the factorization computed by DSYTRF_RK or DSYTRF_BK:
!>
!>     A = P*U*D*(U**T)*(P**T) or A = P*L*D*(L**T)*(P**T),
!>
!> where U (or L) is unit upper (or lower) triangular matrix,
!> U**T (or L**T) is the transpose of U (or L), P is a permutation
!> matrix, P**T is the transpose of P, and D is symmetric and block
!> diagonal with 1-by-1 and 2-by-2 diagonal blocks.
!>
!> DSYTRI_3 sets the leading dimension of the workspace  before calling
!> DSYTRI_3X that actually computes the inverse.  This is the blocked
!> version of the algorithm, calling Level 3 BLAS.
!> 
Parameters
[in]UPLO
!>          UPLO is CHARACTER*1
!>          Specifies whether the details of the factorization are
!>          stored as an upper or lower triangular matrix.
!>          = 'U':  Upper triangle of A is stored;
!>          = 'L':  Lower triangle of A is stored.
!> 
[in]N
!>          N is INTEGER
!>          The order of the matrix A.  N >= 0.
!> 
[in,out]A
!>          A is DOUBLE PRECISION array, dimension (LDA,N)
!>          On entry, diagonal of the block diagonal matrix D and
!>          factors U or L as computed by DSYTRF_RK and DSYTRF_BK:
!>            a) ONLY diagonal elements of the symmetric block diagonal
!>               matrix D on the diagonal of A, i.e. D(k,k) = A(k,k);
!>               (superdiagonal (or subdiagonal) elements of D
!>                should be provided on entry in array E), and
!>            b) If UPLO = 'U': factor U in the superdiagonal part of A.
!>               If UPLO = 'L': factor L in the subdiagonal part of A.
!>
!>          On exit, if INFO = 0, the symmetric inverse of the original
!>          matrix.
!>             If UPLO = 'U': the upper triangular part of the inverse
!>             is formed and the part of A below the diagonal is not
!>             referenced;
!>             If UPLO = 'L': the lower triangular part of the inverse
!>             is formed and the part of A above the diagonal is not
!>             referenced.
!> 
[in]LDA
!>          LDA is INTEGER
!>          The leading dimension of the array A.  LDA >= max(1,N).
!> 
[in]E
!>          E is DOUBLE PRECISION array, dimension (N)
!>          On entry, contains the superdiagonal (or subdiagonal)
!>          elements of the symmetric block diagonal matrix D
!>          with 1-by-1 or 2-by-2 diagonal blocks, where
!>          If UPLO = 'U': E(i) = D(i-1,i),i=2:N, E(1) not referenced;
!>          If UPLO = 'L': E(i) = D(i+1,i),i=1:N-1, E(N) not referenced.
!>
!>          NOTE: For 1-by-1 diagonal block D(k), where
!>          1 <= k <= N, the element E(k) is not referenced in both
!>          UPLO = 'U' or UPLO = 'L' cases.
!> 
[in]IPIV
!>          IPIV is INTEGER array, dimension (N)
!>          Details of the interchanges and the block structure of D
!>          as determined by DSYTRF_RK or DSYTRF_BK.
!> 
[out]WORK
!>          WORK is DOUBLE PRECISION array, dimension (MAX(1,LWORK)).
!>          On exit, if INFO = 0, WORK(1) returns the optimal LWORK.
!> 
[in]LWORK
!>          LWORK is INTEGER
!>          The length of WORK.
!>          If N = 0, LWORK >= 1, else LWORK >= (N+NB+1)*(NB+3).
!>
!>          If LWORK = -1, then a workspace query is assumed;
!>          the routine only calculates the optimal size of the optimal
!>          size of the WORK array, returns this value as the first
!>          entry of the WORK array, and no error message related to
!>          LWORK is issued by XERBLA.
!> 
[out]INFO
!>          INFO is INTEGER
!>          = 0: successful exit
!>          < 0: if INFO = -i, the i-th argument had an illegal value
!>          > 0: if INFO = i, D(i,i) = 0; the matrix is singular and its
!>               inverse could not be computed.
!> 
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Contributors:
!>
!>  November 2017,  Igor Kozachenko,
!>                  Computer Science Division,
!>                  University of California, Berkeley
!>
!> 

Definition at line 167 of file dsytri_3.f.

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*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine dsytri_3x(uplo, n, a, lda, e, ipiv, work, nb, info)
DSYTRI_3X
Definition dsytri_3x.f:158
integer function ilaenv(ispec, name, opts, n1, n2, n3, n4)
ILAENV
Definition ilaenv.f:160
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: