LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
chpt01.f
Go to the documentation of this file.
1*> \brief \b CHPT01
2*
3* =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6* http://www.netlib.org/lapack/explore-html/
7*
8* Definition:
9* ===========
10*
11* SUBROUTINE CHPT01( UPLO, N, A, AFAC, IPIV, C, LDC, RWORK, RESID )
12*
13* .. Scalar Arguments ..
14* CHARACTER UPLO
15* INTEGER LDC, N
16* REAL RESID
17* ..
18* .. Array Arguments ..
19* INTEGER IPIV( * )
20* REAL RWORK( * )
21* COMPLEX A( * ), AFAC( * ), C( LDC, * )
22* ..
23*
24*
25*> \par Purpose:
26* =============
27*>
28*> \verbatim
29*>
30*> CHPT01 reconstructs a Hermitian indefinite packed matrix A from its
31*> block L*D*L' or U*D*U' factorization and computes the residual
32*> norm( C - A ) / ( N * norm(A) * EPS ),
33*> where C is the reconstructed matrix, EPS is the machine epsilon,
34*> L' is the conjugate transpose of L, and U' is the conjugate transpose
35*> of U.
36*> \endverbatim
37*
38* Arguments:
39* ==========
40*
41*> \param[in] UPLO
42*> \verbatim
43*> UPLO is CHARACTER*1
44*> Specifies whether the upper or lower triangular part of the
45*> Hermitian matrix A is stored:
46*> = 'U': Upper triangular
47*> = 'L': Lower triangular
48*> \endverbatim
49*>
50*> \param[in] N
51*> \verbatim
52*> N is INTEGER
53*> The number of rows and columns of the matrix A. N >= 0.
54*> \endverbatim
55*>
56*> \param[in] A
57*> \verbatim
58*> A is COMPLEX array, dimension (N*(N+1)/2)
59*> The original Hermitian matrix A, stored as a packed
60*> triangular matrix.
61*> \endverbatim
62*>
63*> \param[in] AFAC
64*> \verbatim
65*> AFAC is COMPLEX array, dimension (N*(N+1)/2)
66*> The factored form of the matrix A, stored as a packed
67*> triangular matrix. AFAC contains the block diagonal matrix D
68*> and the multipliers used to obtain the factor L or U from the
69*> block L*D*L' or U*D*U' factorization as computed by CHPTRF.
70*> \endverbatim
71*>
72*> \param[in] IPIV
73*> \verbatim
74*> IPIV is INTEGER array, dimension (N)
75*> The pivot indices from CHPTRF.
76*> \endverbatim
77*>
78*> \param[out] C
79*> \verbatim
80*> C is COMPLEX array, dimension (LDC,N)
81*> \endverbatim
82*>
83*> \param[in] LDC
84*> \verbatim
85*> LDC is INTEGER
86*> The leading dimension of the array C. LDC >= max(1,N).
87*> \endverbatim
88*>
89*> \param[out] RWORK
90*> \verbatim
91*> RWORK is REAL array, dimension (N)
92*> \endverbatim
93*>
94*> \param[out] RESID
95*> \verbatim
96*> RESID is REAL
97*> If UPLO = 'L', norm(L*D*L' - A) / ( N * norm(A) * EPS )
98*> If UPLO = 'U', norm(U*D*U' - A) / ( N * norm(A) * EPS )
99*> \endverbatim
100*
101* Authors:
102* ========
103*
104*> \author Univ. of Tennessee
105*> \author Univ. of California Berkeley
106*> \author Univ. of Colorado Denver
107*> \author NAG Ltd.
108*
109*> \ingroup complex_lin
110*
111* =====================================================================
112 SUBROUTINE chpt01( UPLO, N, A, AFAC, IPIV, C, LDC, RWORK, RESID )
113*
114* -- LAPACK test routine --
115* -- LAPACK is a software package provided by Univ. of Tennessee, --
116* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
117*
118* .. Scalar Arguments ..
119 CHARACTER UPLO
120 INTEGER LDC, N
121 REAL RESID
122* ..
123* .. Array Arguments ..
124 INTEGER IPIV( * )
125 REAL RWORK( * )
126 COMPLEX A( * ), AFAC( * ), C( LDC, * )
127* ..
128*
129* =====================================================================
130*
131* .. Parameters ..
132 REAL ZERO, ONE
133 parameter( zero = 0.0e+0, one = 1.0e+0 )
134 COMPLEX CZERO, CONE
135 parameter( czero = ( 0.0e+0, 0.0e+0 ),
136 $ cone = ( 1.0e+0, 0.0e+0 ) )
137* ..
138* .. Local Scalars ..
139 INTEGER I, INFO, J, JC
140 REAL ANORM, EPS
141* ..
142* .. External Functions ..
143 LOGICAL LSAME
144 REAL CLANHE, CLANHP, SLAMCH
145 EXTERNAL lsame, clanhe, clanhp, slamch
146* ..
147* .. External Subroutines ..
148 EXTERNAL clavhp, claset
149* ..
150* .. Intrinsic Functions ..
151 INTRINSIC aimag, real
152* ..
153* .. Executable Statements ..
154*
155* Quick exit if N = 0.
156*
157 IF( n.LE.0 ) THEN
158 resid = zero
159 RETURN
160 END IF
161*
162* Determine EPS and the norm of A.
163*
164 eps = slamch( 'Epsilon' )
165 anorm = clanhp( '1', uplo, n, a, rwork )
166*
167* Check the imaginary parts of the diagonal elements and return with
168* an error code if any are nonzero.
169*
170 jc = 1
171 IF( lsame( uplo, 'U' ) ) THEN
172 DO 10 j = 1, n
173 IF( aimag( afac( jc ) ).NE.zero ) THEN
174 resid = one / eps
175 RETURN
176 END IF
177 jc = jc + j + 1
178 10 CONTINUE
179 ELSE
180 DO 20 j = 1, n
181 IF( aimag( afac( jc ) ).NE.zero ) THEN
182 resid = one / eps
183 RETURN
184 END IF
185 jc = jc + n - j + 1
186 20 CONTINUE
187 END IF
188*
189* Initialize C to the identity matrix.
190*
191 CALL claset( 'Full', n, n, czero, cone, c, ldc )
192*
193* Call CLAVHP to form the product D * U' (or D * L' ).
194*
195 CALL clavhp( uplo, 'Conjugate', 'Non-unit', n, n, afac, ipiv, c,
196 $ ldc, info )
197*
198* Call CLAVHP again to multiply by U ( or L ).
199*
200 CALL clavhp( uplo, 'No transpose', 'Unit', n, n, afac, ipiv, c,
201 $ ldc, info )
202*
203* Compute the difference C - A .
204*
205 IF( lsame( uplo, 'U' ) ) THEN
206 jc = 0
207 DO 40 j = 1, n
208 DO 30 i = 1, j - 1
209 c( i, j ) = c( i, j ) - a( jc+i )
210 30 CONTINUE
211 c( j, j ) = c( j, j ) - real( a( jc+j ) )
212 jc = jc + j
213 40 CONTINUE
214 ELSE
215 jc = 1
216 DO 60 j = 1, n
217 c( j, j ) = c( j, j ) - real( a( jc ) )
218 DO 50 i = j + 1, n
219 c( i, j ) = c( i, j ) - a( jc+i-j )
220 50 CONTINUE
221 jc = jc + n - j + 1
222 60 CONTINUE
223 END IF
224*
225* Compute norm( C - A ) / ( N * norm(A) * EPS )
226*
227 resid = clanhe( '1', uplo, n, c, ldc, rwork )
228*
229 IF( anorm.LE.zero ) THEN
230 IF( resid.NE.zero )
231 $ resid = one / eps
232 ELSE
233 resid = ( ( resid / real( n ) ) / anorm ) / eps
234 END IF
235*
236 RETURN
237*
238* End of CHPT01
239*
240 END
subroutine chpt01(uplo, n, a, afac, ipiv, c, ldc, rwork, resid)
CHPT01
Definition chpt01.f:113
subroutine clavhp(uplo, trans, diag, n, nrhs, a, ipiv, b, ldb, info)
CLAVHP
Definition clavhp.f:131
subroutine claset(uplo, m, n, alpha, beta, a, lda)
CLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values.
Definition claset.f:106