LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zppt01.f
Go to the documentation of this file.
1 *> \brief \b ZPPT01
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 ZPPT01( UPLO, N, A, AFAC, RWORK, RESID )
12 *
13 * .. Scalar Arguments ..
14 * CHARACTER UPLO
15 * INTEGER N
16 * DOUBLE PRECISION RESID
17 * ..
18 * .. Array Arguments ..
19 * DOUBLE PRECISION RWORK( * )
20 * COMPLEX*16 A( * ), AFAC( * )
21 * ..
22 *
23 *
24 *> \par Purpose:
25 * =============
26 *>
27 *> \verbatim
28 *>
29 *> ZPPT01 reconstructs a Hermitian positive definite packed matrix A
30 *> from its L*L' or U'*U factorization and computes the residual
31 *> norm( L*L' - A ) / ( N * norm(A) * EPS ) or
32 *> norm( U'*U - A ) / ( N * norm(A) * EPS ),
33 *> where EPS is the machine epsilon, L' is the conjugate transpose of
34 *> L, and U' is the conjugate transpose of U.
35 *> \endverbatim
36 *
37 * Arguments:
38 * ==========
39 *
40 *> \param[in] UPLO
41 *> \verbatim
42 *> UPLO is CHARACTER*1
43 *> Specifies whether the upper or lower triangular part of the
44 *> Hermitian matrix A is stored:
45 *> = 'U': Upper triangular
46 *> = 'L': Lower triangular
47 *> \endverbatim
48 *>
49 *> \param[in] N
50 *> \verbatim
51 *> N is INTEGER
52 *> The number of rows and columns of the matrix A. N >= 0.
53 *> \endverbatim
54 *>
55 *> \param[in] A
56 *> \verbatim
57 *> A is COMPLEX*16 array, dimension (N*(N+1)/2)
58 *> The original Hermitian matrix A, stored as a packed
59 *> triangular matrix.
60 *> \endverbatim
61 *>
62 *> \param[in,out] AFAC
63 *> \verbatim
64 *> AFAC is COMPLEX*16 array, dimension (N*(N+1)/2)
65 *> On entry, the factor L or U from the L*L' or U'*U
66 *> factorization of A, stored as a packed triangular matrix.
67 *> Overwritten with the reconstructed matrix, and then with the
68 *> difference L*L' - A (or U'*U - A).
69 *> \endverbatim
70 *>
71 *> \param[out] RWORK
72 *> \verbatim
73 *> RWORK is DOUBLE PRECISION array, dimension (N)
74 *> \endverbatim
75 *>
76 *> \param[out] RESID
77 *> \verbatim
78 *> RESID is DOUBLE PRECISION
79 *> If UPLO = 'L', norm(L*L' - A) / ( N * norm(A) * EPS )
80 *> If UPLO = 'U', norm(U'*U - A) / ( N * norm(A) * EPS )
81 *> \endverbatim
82 *
83 * Authors:
84 * ========
85 *
86 *> \author Univ. of Tennessee
87 *> \author Univ. of California Berkeley
88 *> \author Univ. of Colorado Denver
89 *> \author NAG Ltd.
90 *
91 *> \date November 2011
92 *
93 *> \ingroup complex16_lin
94 *
95 * =====================================================================
96  SUBROUTINE zppt01( UPLO, N, A, AFAC, RWORK, RESID )
97 *
98 * -- LAPACK test routine (version 3.4.0) --
99 * -- LAPACK is a software package provided by Univ. of Tennessee, --
100 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
101 * November 2011
102 *
103 * .. Scalar Arguments ..
104  CHARACTER UPLO
105  INTEGER N
106  DOUBLE PRECISION RESID
107 * ..
108 * .. Array Arguments ..
109  DOUBLE PRECISION RWORK( * )
110  COMPLEX*16 A( * ), AFAC( * )
111 * ..
112 *
113 * =====================================================================
114 *
115 * .. Parameters ..
116  DOUBLE PRECISION ZERO, ONE
117  parameter ( zero = 0.0d+0, one = 1.0d+0 )
118 * ..
119 * .. Local Scalars ..
120  INTEGER I, K, KC
121  DOUBLE PRECISION ANORM, EPS, TR
122  COMPLEX*16 TC
123 * ..
124 * .. External Functions ..
125  LOGICAL LSAME
126  DOUBLE PRECISION DLAMCH, ZLANHP
127  COMPLEX*16 ZDOTC
128  EXTERNAL lsame, dlamch, zlanhp, zdotc
129 * ..
130 * .. External Subroutines ..
131  EXTERNAL zhpr, zscal, ztpmv
132 * ..
133 * .. Intrinsic Functions ..
134  INTRINSIC dble, dimag
135 * ..
136 * .. Executable Statements ..
137 *
138 * Quick exit if N = 0
139 *
140  IF( n.LE.0 ) THEN
141  resid = zero
142  RETURN
143  END IF
144 *
145 * Exit with RESID = 1/EPS if ANORM = 0.
146 *
147  eps = dlamch( 'Epsilon' )
148  anorm = zlanhp( '1', uplo, n, a, rwork )
149  IF( anorm.LE.zero ) THEN
150  resid = one / eps
151  RETURN
152  END IF
153 *
154 * Check the imaginary parts of the diagonal elements and return with
155 * an error code if any are nonzero.
156 *
157  kc = 1
158  IF( lsame( uplo, 'U' ) ) THEN
159  DO 10 k = 1, n
160  IF( dimag( afac( kc ) ).NE.zero ) THEN
161  resid = one / eps
162  RETURN
163  END IF
164  kc = kc + k + 1
165  10 CONTINUE
166  ELSE
167  DO 20 k = 1, n
168  IF( dimag( afac( kc ) ).NE.zero ) THEN
169  resid = one / eps
170  RETURN
171  END IF
172  kc = kc + n - k + 1
173  20 CONTINUE
174  END IF
175 *
176 * Compute the product U'*U, overwriting U.
177 *
178  IF( lsame( uplo, 'U' ) ) THEN
179  kc = ( n*( n-1 ) ) / 2 + 1
180  DO 30 k = n, 1, -1
181 *
182 * Compute the (K,K) element of the result.
183 *
184  tr = zdotc( k, afac( kc ), 1, afac( kc ), 1 )
185  afac( kc+k-1 ) = tr
186 *
187 * Compute the rest of column K.
188 *
189  IF( k.GT.1 ) THEN
190  CALL ztpmv( 'Upper', 'Conjugate', 'Non-unit', k-1, afac,
191  $ afac( kc ), 1 )
192  kc = kc - ( k-1 )
193  END IF
194  30 CONTINUE
195 *
196 * Compute the difference L*L' - A
197 *
198  kc = 1
199  DO 50 k = 1, n
200  DO 40 i = 1, k - 1
201  afac( kc+i-1 ) = afac( kc+i-1 ) - a( kc+i-1 )
202  40 CONTINUE
203  afac( kc+k-1 ) = afac( kc+k-1 ) - dble( a( kc+k-1 ) )
204  kc = kc + k
205  50 CONTINUE
206 *
207 * Compute the product L*L', overwriting L.
208 *
209  ELSE
210  kc = ( n*( n+1 ) ) / 2
211  DO 60 k = n, 1, -1
212 *
213 * Add a multiple of column K of the factor L to each of
214 * columns K+1 through N.
215 *
216  IF( k.LT.n )
217  $ CALL zhpr( 'Lower', n-k, one, afac( kc+1 ), 1,
218  $ afac( kc+n-k+1 ) )
219 *
220 * Scale column K by the diagonal element.
221 *
222  tc = afac( kc )
223  CALL zscal( n-k+1, tc, afac( kc ), 1 )
224 *
225  kc = kc - ( n-k+2 )
226  60 CONTINUE
227 *
228 * Compute the difference U'*U - A
229 *
230  kc = 1
231  DO 80 k = 1, n
232  afac( kc ) = afac( kc ) - dble( a( kc ) )
233  DO 70 i = k + 1, n
234  afac( kc+i-k ) = afac( kc+i-k ) - a( kc+i-k )
235  70 CONTINUE
236  kc = kc + n - k + 1
237  80 CONTINUE
238  END IF
239 *
240 * Compute norm( L*U - A ) / ( N * norm(A) * EPS )
241 *
242  resid = zlanhp( '1', uplo, n, afac, rwork )
243 *
244  resid = ( ( resid / dble( n ) ) / anorm ) / eps
245 *
246  RETURN
247 *
248 * End of ZPPT01
249 *
250  END
subroutine ztpmv(UPLO, TRANS, DIAG, N, AP, X, INCX)
ZTPMV
Definition: ztpmv.f:144
subroutine zhpr(UPLO, N, ALPHA, X, INCX, AP)
ZHPR
Definition: zhpr.f:132
subroutine zppt01(UPLO, N, A, AFAC, RWORK, RESID)
ZPPT01
Definition: zppt01.f:97
subroutine zscal(N, ZA, ZX, INCX)
ZSCAL
Definition: zscal.f:54