LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zhpt01.f
Go to the documentation of this file.
1 *> \brief \b ZHPT01
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 ZHPT01( UPLO, N, A, AFAC, IPIV, C, LDC, RWORK, RESID )
12 *
13 * .. Scalar Arguments ..
14 * CHARACTER UPLO
15 * INTEGER LDC, N
16 * DOUBLE PRECISION RESID
17 * ..
18 * .. Array Arguments ..
19 * INTEGER IPIV( * )
20 * DOUBLE PRECISION RWORK( * )
21 * COMPLEX*16 A( * ), AFAC( * ), C( LDC, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> ZHPT01 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*16 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*16 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 ZHPTRF.
70 *> \endverbatim
71 *>
72 *> \param[in] IPIV
73 *> \verbatim
74 *> IPIV is INTEGER array, dimension (N)
75 *> The pivot indices from ZHPTRF.
76 *> \endverbatim
77 *>
78 *> \param[out] C
79 *> \verbatim
80 *> C is COMPLEX*16 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 DOUBLE PRECISION array, dimension (N)
92 *> \endverbatim
93 *>
94 *> \param[out] RESID
95 *> \verbatim
96 *> RESID is DOUBLE PRECISION
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 *> \date November 2011
110 *
111 *> \ingroup complex16_lin
112 *
113 * =====================================================================
114  SUBROUTINE zhpt01( UPLO, N, A, AFAC, IPIV, C, LDC, RWORK, RESID )
115 *
116 * -- LAPACK test routine (version 3.4.0) --
117 * -- LAPACK is a software package provided by Univ. of Tennessee, --
118 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
119 * November 2011
120 *
121 * .. Scalar Arguments ..
122  CHARACTER UPLO
123  INTEGER LDC, N
124  DOUBLE PRECISION RESID
125 * ..
126 * .. Array Arguments ..
127  INTEGER IPIV( * )
128  DOUBLE PRECISION RWORK( * )
129  COMPLEX*16 A( * ), AFAC( * ), C( ldc, * )
130 * ..
131 *
132 * =====================================================================
133 *
134 * .. Parameters ..
135  DOUBLE PRECISION ZERO, ONE
136  parameter ( zero = 0.0d+0, one = 1.0d+0 )
137  COMPLEX*16 CZERO, CONE
138  parameter ( czero = ( 0.0d+0, 0.0d+0 ),
139  $ cone = ( 1.0d+0, 0.0d+0 ) )
140 * ..
141 * .. Local Scalars ..
142  INTEGER I, INFO, J, JC
143  DOUBLE PRECISION ANORM, EPS
144 * ..
145 * .. External Functions ..
146  LOGICAL LSAME
147  DOUBLE PRECISION DLAMCH, ZLANHE, ZLANHP
148  EXTERNAL lsame, dlamch, zlanhe, zlanhp
149 * ..
150 * .. External Subroutines ..
151  EXTERNAL zlaset, zlavhp
152 * ..
153 * .. Intrinsic Functions ..
154  INTRINSIC dble, dimag
155 * ..
156 * .. Executable Statements ..
157 *
158 * Quick exit if N = 0.
159 *
160  IF( n.LE.0 ) THEN
161  resid = zero
162  RETURN
163  END IF
164 *
165 * Determine EPS and the norm of A.
166 *
167  eps = dlamch( 'Epsilon' )
168  anorm = zlanhp( '1', uplo, n, a, rwork )
169 *
170 * Check the imaginary parts of the diagonal elements and return with
171 * an error code if any are nonzero.
172 *
173  jc = 1
174  IF( lsame( uplo, 'U' ) ) THEN
175  DO 10 j = 1, n
176  IF( dimag( afac( jc ) ).NE.zero ) THEN
177  resid = one / eps
178  RETURN
179  END IF
180  jc = jc + j + 1
181  10 CONTINUE
182  ELSE
183  DO 20 j = 1, n
184  IF( dimag( afac( jc ) ).NE.zero ) THEN
185  resid = one / eps
186  RETURN
187  END IF
188  jc = jc + n - j + 1
189  20 CONTINUE
190  END IF
191 *
192 * Initialize C to the identity matrix.
193 *
194  CALL zlaset( 'Full', n, n, czero, cone, c, ldc )
195 *
196 * Call ZLAVHP to form the product D * U' (or D * L' ).
197 *
198  CALL zlavhp( uplo, 'Conjugate', 'Non-unit', n, n, afac, ipiv, c,
199  $ ldc, info )
200 *
201 * Call ZLAVHP again to multiply by U ( or L ).
202 *
203  CALL zlavhp( uplo, 'No transpose', 'Unit', n, n, afac, ipiv, c,
204  $ ldc, info )
205 *
206 * Compute the difference C - A .
207 *
208  IF( lsame( uplo, 'U' ) ) THEN
209  jc = 0
210  DO 40 j = 1, n
211  DO 30 i = 1, j - 1
212  c( i, j ) = c( i, j ) - a( jc+i )
213  30 CONTINUE
214  c( j, j ) = c( j, j ) - dble( a( jc+j ) )
215  jc = jc + j
216  40 CONTINUE
217  ELSE
218  jc = 1
219  DO 60 j = 1, n
220  c( j, j ) = c( j, j ) - dble( a( jc ) )
221  DO 50 i = j + 1, n
222  c( i, j ) = c( i, j ) - a( jc+i-j )
223  50 CONTINUE
224  jc = jc + n - j + 1
225  60 CONTINUE
226  END IF
227 *
228 * Compute norm( C - A ) / ( N * norm(A) * EPS )
229 *
230  resid = zlanhe( '1', uplo, n, c, ldc, rwork )
231 *
232  IF( anorm.LE.zero ) THEN
233  IF( resid.NE.zero )
234  $ resid = one / eps
235  ELSE
236  resid = ( ( resid / dble( n ) ) / anorm ) / eps
237  END IF
238 *
239  RETURN
240 *
241 * End of ZHPT01
242 *
243  END
subroutine zlaset(UPLO, M, N, ALPHA, BETA, A, LDA)
ZLASET initializes the off-diagonal elements and the diagonal elements of a matrix to given values...
Definition: zlaset.f:108
subroutine zlavhp(UPLO, TRANS, DIAG, N, NRHS, A, IPIV, B, LDB, INFO)
ZLAVHP
Definition: zlavhp.f:133
subroutine zhpt01(UPLO, N, A, AFAC, IPIV, C, LDC, RWORK, RESID)
ZHPT01
Definition: zhpt01.f:115