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