LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
cpst01.f
Go to the documentation of this file.
1 *> \brief \b CPST01
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 CPST01( UPLO, N, A, LDA, AFAC, LDAFAC, PERM, LDPERM,
12 * PIV, RWORK, RESID, RANK )
13 *
14 * .. Scalar Arguments ..
15 * REAL RESID
16 * INTEGER LDA, LDAFAC, LDPERM, N, RANK
17 * CHARACTER UPLO
18 * ..
19 * .. Array Arguments ..
20 * COMPLEX A( LDA, * ), AFAC( LDAFAC, * ),
21 * $ PERM( LDPERM, * )
22 * REAL RWORK( * )
23 * INTEGER PIV( * )
24 * ..
25 *
26 *
27 *> \par Purpose:
28 * =============
29 *>
30 *> \verbatim
31 *>
32 *> CPST01 reconstructs an Hermitian positive semidefinite matrix A
33 *> from its L or U factors and the permutation matrix P and computes
34 *> the residual
35 *> norm( P*L*L'*P' - A ) / ( N * norm(A) * EPS ) or
36 *> norm( P*U'*U*P' - A ) / ( N * norm(A) * EPS ),
37 *> where EPS is the machine epsilon, L' is the conjugate transpose of L,
38 *> and U' is the conjugate transpose of U.
39 *> \endverbatim
40 *
41 * Arguments:
42 * ==========
43 *
44 *> \param[in] UPLO
45 *> \verbatim
46 *> UPLO is CHARACTER*1
47 *> Specifies whether the upper or lower triangular part of the
48 *> Hermitian matrix A is stored:
49 *> = 'U': Upper triangular
50 *> = 'L': Lower triangular
51 *> \endverbatim
52 *>
53 *> \param[in] N
54 *> \verbatim
55 *> N is INTEGER
56 *> The number of rows and columns of the matrix A. N >= 0.
57 *> \endverbatim
58 *>
59 *> \param[in] A
60 *> \verbatim
61 *> A is COMPLEX array, dimension (LDA,N)
62 *> The original Hermitian matrix A.
63 *> \endverbatim
64 *>
65 *> \param[in] LDA
66 *> \verbatim
67 *> LDA is INTEGER
68 *> The leading dimension of the array A. LDA >= max(1,N)
69 *> \endverbatim
70 *>
71 *> \param[in] AFAC
72 *> \verbatim
73 *> AFAC is COMPLEX array, dimension (LDAFAC,N)
74 *> The factor L or U from the L*L' or U'*U
75 *> factorization of A.
76 *> \endverbatim
77 *>
78 *> \param[in] LDAFAC
79 *> \verbatim
80 *> LDAFAC is INTEGER
81 *> The leading dimension of the array AFAC. LDAFAC >= max(1,N).
82 *> \endverbatim
83 *>
84 *> \param[out] PERM
85 *> \verbatim
86 *> PERM is COMPLEX array, dimension (LDPERM,N)
87 *> Overwritten with the reconstructed matrix, and then with the
88 *> difference P*L*L'*P' - A (or P*U'*U*P' - A)
89 *> \endverbatim
90 *>
91 *> \param[in] LDPERM
92 *> \verbatim
93 *> LDPERM is INTEGER
94 *> The leading dimension of the array PERM.
95 *> LDAPERM >= max(1,N).
96 *> \endverbatim
97 *>
98 *> \param[in] PIV
99 *> \verbatim
100 *> PIV is INTEGER array, dimension (N)
101 *> PIV is such that the nonzero entries are
102 *> P( PIV( K ), K ) = 1.
103 *> \endverbatim
104 *>
105 *> \param[out] RWORK
106 *> \verbatim
107 *> RWORK is REAL array, dimension (N)
108 *> \endverbatim
109 *>
110 *> \param[out] RESID
111 *> \verbatim
112 *> RESID is REAL
113 *> If UPLO = 'L', norm(L*L' - A) / ( N * norm(A) * EPS )
114 *> If UPLO = 'U', norm(U'*U - A) / ( N * norm(A) * EPS )
115 *> \endverbatim
116 *>
117 *> \param[in] RANK
118 *> \verbatim
119 *> RANK is INTEGER
120 *> number of nonzero singular values of A.
121 *> \endverbatim
122 *
123 * Authors:
124 * ========
125 *
126 *> \author Univ. of Tennessee
127 *> \author Univ. of California Berkeley
128 *> \author Univ. of Colorado Denver
129 *> \author NAG Ltd.
130 *
131 *> \date November 2011
132 *
133 *> \ingroup complex_lin
134 *
135 * =====================================================================
136  SUBROUTINE cpst01( UPLO, N, A, LDA, AFAC, LDAFAC, PERM, LDPERM,
137  $ piv, rwork, resid, rank )
138 *
139 * -- LAPACK test routine (version 3.4.0) --
140 * -- LAPACK is a software package provided by Univ. of Tennessee, --
141 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
142 * November 2011
143 *
144 * .. Scalar Arguments ..
145  REAL resid
146  INTEGER lda, ldafac, ldperm, n, rank
147  CHARACTER uplo
148 * ..
149 * .. Array Arguments ..
150  COMPLEX a( lda, * ), afac( ldafac, * ),
151  $ perm( ldperm, * )
152  REAL rwork( * )
153  INTEGER piv( * )
154 * ..
155 *
156 * =====================================================================
157 *
158 * .. Parameters ..
159  REAL zero, one
160  parameter( zero = 0.0e+0, one = 1.0e+0 )
161  COMPLEX czero
162  parameter( czero = ( 0.0e+0, 0.0e+0 ) )
163 * ..
164 * .. Local Scalars ..
165  COMPLEX tc
166  REAL anorm, eps, tr
167  INTEGER i, j, k
168 * ..
169 * .. External Functions ..
170  COMPLEX cdotc
171  REAL clanhe, slamch
172  LOGICAL lsame
173  EXTERNAL cdotc, clanhe, slamch, lsame
174 * ..
175 * .. External Subroutines ..
176  EXTERNAL cher, cscal, ctrmv
177 * ..
178 * .. Intrinsic Functions ..
179  INTRINSIC aimag, conjg, real
180 * ..
181 * .. Executable Statements ..
182 *
183 * Quick exit if N = 0.
184 *
185  IF( n.LE.0 ) THEN
186  resid = zero
187  return
188  END IF
189 *
190 * Exit with RESID = 1/EPS if ANORM = 0.
191 *
192  eps = slamch( 'Epsilon' )
193  anorm = clanhe( '1', uplo, n, a, lda, rwork )
194  IF( anorm.LE.zero ) THEN
195  resid = one / eps
196  return
197  END IF
198 *
199 * Check the imaginary parts of the diagonal elements and return with
200 * an error code if any are nonzero.
201 *
202  DO 100 j = 1, n
203  IF( aimag( afac( j, j ) ).NE.zero ) THEN
204  resid = one / eps
205  return
206  END IF
207  100 continue
208 *
209 * Compute the product U'*U, overwriting U.
210 *
211  IF( lsame( uplo, 'U' ) ) THEN
212 *
213  IF( rank.LT.n ) THEN
214  DO 120 j = rank + 1, n
215  DO 110 i = rank + 1, j
216  afac( i, j ) = czero
217  110 continue
218  120 continue
219  END IF
220 *
221  DO 130 k = n, 1, -1
222 *
223 * Compute the (K,K) element of the result.
224 *
225  tr = cdotc( k, afac( 1, k ), 1, afac( 1, k ), 1 )
226  afac( k, k ) = tr
227 *
228 * Compute the rest of column K.
229 *
230  CALL ctrmv( 'Upper', 'Conjugate', 'Non-unit', k-1, afac,
231  $ ldafac, afac( 1, k ), 1 )
232 *
233  130 continue
234 *
235 * Compute the product L*L', overwriting L.
236 *
237  ELSE
238 *
239  IF( rank.LT.n ) THEN
240  DO 150 j = rank + 1, n
241  DO 140 i = j, n
242  afac( i, j ) = czero
243  140 continue
244  150 continue
245  END IF
246 *
247  DO 160 k = n, 1, -1
248 * Add a multiple of column K of the factor L to each of
249 * columns K+1 through N.
250 *
251  IF( k+1.LE.n )
252  $ CALL cher( 'Lower', n-k, one, afac( k+1, k ), 1,
253  $ afac( k+1, k+1 ), ldafac )
254 *
255 * Scale column K by the diagonal element.
256 *
257  tc = afac( k, k )
258  CALL cscal( n-k+1, tc, afac( k, k ), 1 )
259  160 continue
260 *
261  END IF
262 *
263 * Form P*L*L'*P' or P*U'*U*P'
264 *
265  IF( lsame( uplo, 'U' ) ) THEN
266 *
267  DO 180 j = 1, n
268  DO 170 i = 1, n
269  IF( piv( i ).LE.piv( j ) ) THEN
270  IF( i.LE.j ) THEN
271  perm( piv( i ), piv( j ) ) = afac( i, j )
272  ELSE
273  perm( piv( i ), piv( j ) ) = conjg( afac( j, i ) )
274  END IF
275  END IF
276  170 continue
277  180 continue
278 *
279 *
280  ELSE
281 *
282  DO 200 j = 1, n
283  DO 190 i = 1, n
284  IF( piv( i ).GE.piv( j ) ) THEN
285  IF( i.GE.j ) THEN
286  perm( piv( i ), piv( j ) ) = afac( i, j )
287  ELSE
288  perm( piv( i ), piv( j ) ) = conjg( afac( j, i ) )
289  END IF
290  END IF
291  190 continue
292  200 continue
293 *
294  END IF
295 *
296 * Compute the difference P*L*L'*P' - A (or P*U'*U*P' - A).
297 *
298  IF( lsame( uplo, 'U' ) ) THEN
299  DO 220 j = 1, n
300  DO 210 i = 1, j - 1
301  perm( i, j ) = perm( i, j ) - a( i, j )
302  210 continue
303  perm( j, j ) = perm( j, j ) - REAL( A( J, J ) )
304  220 continue
305  ELSE
306  DO 240 j = 1, n
307  perm( j, j ) = perm( j, j ) - REAL( A( J, J ) )
308  DO 230 i = j + 1, n
309  perm( i, j ) = perm( i, j ) - a( i, j )
310  230 continue
311  240 continue
312  END IF
313 *
314 * Compute norm( P*L*L'P - A ) / ( N * norm(A) * EPS ), or
315 * ( P*U'*U*P' - A )/ ( N * norm(A) * EPS ).
316 *
317  resid = clanhe( '1', uplo, n, perm, ldafac, rwork )
318 *
319  resid = ( ( resid / REAL( N ) ) / anorm ) / eps
320 *
321  return
322 *
323 * End of CPST01
324 *
325  END