LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
cpotri.f
Go to the documentation of this file.
1*> \brief \b CPOTRI
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8*> Download CPOTRI + dependencies
9*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cpotri.f">
10*> [TGZ]</a>
11*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cpotri.f">
12*> [ZIP]</a>
13*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cpotri.f">
14*> [TXT]</a>
15*
16* Definition:
17* ===========
18*
19* SUBROUTINE CPOTRI( UPLO, N, A, LDA, INFO )
20*
21* .. Scalar Arguments ..
22* CHARACTER UPLO
23* INTEGER INFO, LDA, N
24* ..
25* .. Array Arguments ..
26* COMPLEX A( LDA, * )
27* ..
28*
29*
30*> \par Purpose:
31* =============
32*>
33*> \verbatim
34*>
35*> CPOTRI computes the inverse of a complex Hermitian positive definite
36*> matrix A using the Cholesky factorization A = U**H*U or A = L*L**H
37*> computed by CPOTRF.
38*> \endverbatim
39*
40* Arguments:
41* ==========
42*
43*> \param[in] UPLO
44*> \verbatim
45*> UPLO is CHARACTER*1
46*> = 'U': Upper triangle of A is stored;
47*> = 'L': Lower triangle of A is stored.
48*> \endverbatim
49*>
50*> \param[in] N
51*> \verbatim
52*> N is INTEGER
53*> The order of the matrix A. N >= 0.
54*> \endverbatim
55*>
56*> \param[in,out] A
57*> \verbatim
58*> A is COMPLEX array, dimension (LDA,N)
59*> On entry, the triangular factor U or L from the Cholesky
60*> factorization A = U**H*U or A = L*L**H, as computed by
61*> CPOTRF.
62*> On exit, the upper or lower triangle of the (Hermitian)
63*> inverse of A, overwriting the input factor U or L.
64*> \endverbatim
65*>
66*> \param[in] LDA
67*> \verbatim
68*> LDA is INTEGER
69*> The leading dimension of the array A. LDA >= max(1,N).
70*> \endverbatim
71*>
72*> \param[out] INFO
73*> \verbatim
74*> INFO is INTEGER
75*> = 0: successful exit
76*> < 0: if INFO = -i, the i-th argument had an illegal value
77*> > 0: if INFO = i, the (i,i) element of the factor U or L is
78*> zero, and the inverse could not be computed.
79*> \endverbatim
80*
81* Authors:
82* ========
83*
84*> \author Univ. of Tennessee
85*> \author Univ. of California Berkeley
86*> \author Univ. of Colorado Denver
87*> \author NAG Ltd.
88*
89*> \ingroup potri
90*
91* =====================================================================
92 SUBROUTINE cpotri( UPLO, N, A, LDA, INFO )
93*
94* -- LAPACK computational routine --
95* -- LAPACK is a software package provided by Univ. of Tennessee, --
96* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
97*
98* .. Scalar Arguments ..
99 CHARACTER UPLO
100 INTEGER INFO, LDA, N
101* ..
102* .. Array Arguments ..
103 COMPLEX A( LDA, * )
104* ..
105*
106* =====================================================================
107*
108* .. External Functions ..
109 LOGICAL LSAME
110 EXTERNAL lsame
111* ..
112* .. External Subroutines ..
113 EXTERNAL clauum, ctrtri, xerbla
114* ..
115* .. Intrinsic Functions ..
116 INTRINSIC max
117* ..
118* .. Executable Statements ..
119*
120* Test the input parameters.
121*
122 info = 0
123 IF( .NOT.lsame( uplo, 'U' ) .AND.
124 $ .NOT.lsame( uplo, 'L' ) ) THEN
125 info = -1
126 ELSE IF( n.LT.0 ) THEN
127 info = -2
128 ELSE IF( lda.LT.max( 1, n ) ) THEN
129 info = -4
130 END IF
131 IF( info.NE.0 ) THEN
132 CALL xerbla( 'CPOTRI', -info )
133 RETURN
134 END IF
135*
136* Quick return if possible
137*
138 IF( n.EQ.0 )
139 $ RETURN
140*
141* Invert the triangular Cholesky factor U or L.
142*
143 CALL ctrtri( uplo, 'Non-unit', n, a, lda, info )
144 IF( info.GT.0 )
145 $ RETURN
146*
147* Form inv(U) * inv(U)**H or inv(L)**H * inv(L).
148*
149 CALL clauum( uplo, n, a, lda, info )
150*
151 RETURN
152*
153* End of CPOTRI
154*
155 END
subroutine xerbla(srname, info)
Definition cblat2.f:3285
subroutine clauum(uplo, n, a, lda, info)
CLAUUM computes the product UUH or LHL, where U and L are upper or lower triangular matrices (blocked...
Definition clauum.f:100
subroutine cpotri(uplo, n, a, lda, info)
CPOTRI
Definition cpotri.f:93
subroutine ctrtri(uplo, diag, n, a, lda, info)
CTRTRI
Definition ctrtri.f:107