LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zppt03.f
Go to the documentation of this file.
1 *> \brief \b ZPPT03
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 ZPPT03( UPLO, N, A, AINV, WORK, LDWORK, RWORK, RCOND,
12 * RESID )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER UPLO
16 * INTEGER LDWORK, N
17 * DOUBLE PRECISION RCOND, RESID
18 * ..
19 * .. Array Arguments ..
20 * DOUBLE PRECISION RWORK( * )
21 * COMPLEX*16 A( * ), AINV( * ), WORK( LDWORK, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> ZPPT03 computes the residual for a Hermitian packed matrix times its
31 *> inverse:
32 *> norm( I - A*AINV ) / ( N * norm(A) * norm(AINV) * EPS ),
33 *> where EPS is the machine epsilon.
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] UPLO
40 *> \verbatim
41 *> UPLO is CHARACTER*1
42 *> Specifies whether the upper or lower triangular part of the
43 *> Hermitian matrix A is stored:
44 *> = 'U': Upper triangular
45 *> = 'L': Lower triangular
46 *> \endverbatim
47 *>
48 *> \param[in] N
49 *> \verbatim
50 *> N is INTEGER
51 *> The number of rows and columns of the matrix A. N >= 0.
52 *> \endverbatim
53 *>
54 *> \param[in] A
55 *> \verbatim
56 *> A is COMPLEX*16 array, dimension (N*(N+1)/2)
57 *> The original Hermitian matrix A, stored as a packed
58 *> triangular matrix.
59 *> \endverbatim
60 *>
61 *> \param[in] AINV
62 *> \verbatim
63 *> AINV is COMPLEX*16 array, dimension (N*(N+1)/2)
64 *> The (Hermitian) inverse of the matrix A, stored as a packed
65 *> triangular matrix.
66 *> \endverbatim
67 *>
68 *> \param[out] WORK
69 *> \verbatim
70 *> WORK is COMPLEX*16 array, dimension (LDWORK,N)
71 *> \endverbatim
72 *>
73 *> \param[in] LDWORK
74 *> \verbatim
75 *> LDWORK is INTEGER
76 *> The leading dimension of the array WORK. LDWORK >= max(1,N).
77 *> \endverbatim
78 *>
79 *> \param[out] RWORK
80 *> \verbatim
81 *> RWORK is DOUBLE PRECISION array, dimension (N)
82 *> \endverbatim
83 *>
84 *> \param[out] RCOND
85 *> \verbatim
86 *> RCOND is DOUBLE PRECISION
87 *> The reciprocal of the condition number of A, computed as
88 *> ( 1/norm(A) ) / norm(AINV).
89 *> \endverbatim
90 *>
91 *> \param[out] RESID
92 *> \verbatim
93 *> RESID is DOUBLE PRECISION
94 *> norm(I - A*AINV) / ( N * norm(A) * norm(AINV) * EPS )
95 *> \endverbatim
96 *
97 * Authors:
98 * ========
99 *
100 *> \author Univ. of Tennessee
101 *> \author Univ. of California Berkeley
102 *> \author Univ. of Colorado Denver
103 *> \author NAG Ltd.
104 *
105 *> \date November 2011
106 *
107 *> \ingroup complex16_lin
108 *
109 * =====================================================================
110  SUBROUTINE zppt03( UPLO, N, A, AINV, WORK, LDWORK, RWORK, RCOND,
111  $ resid )
112 *
113 * -- LAPACK test routine (version 3.4.0) --
114 * -- LAPACK is a software package provided by Univ. of Tennessee, --
115 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
116 * November 2011
117 *
118 * .. Scalar Arguments ..
119  CHARACTER UPLO
120  INTEGER LDWORK, N
121  DOUBLE PRECISION RCOND, RESID
122 * ..
123 * .. Array Arguments ..
124  DOUBLE PRECISION RWORK( * )
125  COMPLEX*16 A( * ), AINV( * ), WORK( ldwork, * )
126 * ..
127 *
128 * =====================================================================
129 *
130 * .. Parameters ..
131  DOUBLE PRECISION ZERO, ONE
132  parameter ( zero = 0.0d+0, one = 1.0d+0 )
133  COMPLEX*16 CZERO, CONE
134  parameter ( czero = ( 0.0d+0, 0.0d+0 ),
135  $ cone = ( 1.0d+0, 0.0d+0 ) )
136 * ..
137 * .. Local Scalars ..
138  INTEGER I, J, JJ
139  DOUBLE PRECISION AINVNM, ANORM, EPS
140 * ..
141 * .. External Functions ..
142  LOGICAL LSAME
143  DOUBLE PRECISION DLAMCH, ZLANGE, ZLANHP
144  EXTERNAL lsame, dlamch, zlange, zlanhp
145 * ..
146 * .. Intrinsic Functions ..
147  INTRINSIC dble, dconjg
148 * ..
149 * .. External Subroutines ..
150  EXTERNAL zcopy, zhpmv
151 * ..
152 * .. Executable Statements ..
153 *
154 * Quick exit if N = 0.
155 *
156  IF( n.LE.0 ) THEN
157  rcond = one
158  resid = zero
159  RETURN
160  END IF
161 *
162 * Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
163 *
164  eps = dlamch( 'Epsilon' )
165  anorm = zlanhp( '1', uplo, n, a, rwork )
166  ainvnm = zlanhp( '1', uplo, n, ainv, rwork )
167  IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
168  rcond = zero
169  resid = one / eps
170  RETURN
171  END IF
172  rcond = ( one / anorm ) / ainvnm
173 *
174 * UPLO = 'U':
175 * Copy the leading N-1 x N-1 submatrix of AINV to WORK(1:N,2:N) and
176 * expand it to a full matrix, then multiply by A one column at a
177 * time, moving the result one column to the left.
178 *
179  IF( lsame( uplo, 'U' ) ) THEN
180 *
181 * Copy AINV
182 *
183  jj = 1
184  DO 20 j = 1, n - 1
185  CALL zcopy( j, ainv( jj ), 1, work( 1, j+1 ), 1 )
186  DO 10 i = 1, j - 1
187  work( j, i+1 ) = dconjg( ainv( jj+i-1 ) )
188  10 CONTINUE
189  jj = jj + j
190  20 CONTINUE
191  jj = ( ( n-1 )*n ) / 2 + 1
192  DO 30 i = 1, n - 1
193  work( n, i+1 ) = dconjg( ainv( jj+i-1 ) )
194  30 CONTINUE
195 *
196 * Multiply by A
197 *
198  DO 40 j = 1, n - 1
199  CALL zhpmv( 'Upper', n, -cone, a, work( 1, j+1 ), 1, czero,
200  $ work( 1, j ), 1 )
201  40 CONTINUE
202  CALL zhpmv( 'Upper', n, -cone, a, ainv( jj ), 1, czero,
203  $ work( 1, n ), 1 )
204 *
205 * UPLO = 'L':
206 * Copy the trailing N-1 x N-1 submatrix of AINV to WORK(1:N,1:N-1)
207 * and multiply by A, moving each column to the right.
208 *
209  ELSE
210 *
211 * Copy AINV
212 *
213  DO 50 i = 1, n - 1
214  work( 1, i ) = dconjg( ainv( i+1 ) )
215  50 CONTINUE
216  jj = n + 1
217  DO 70 j = 2, n
218  CALL zcopy( n-j+1, ainv( jj ), 1, work( j, j-1 ), 1 )
219  DO 60 i = 1, n - j
220  work( j, j+i-1 ) = dconjg( ainv( jj+i ) )
221  60 CONTINUE
222  jj = jj + n - j + 1
223  70 CONTINUE
224 *
225 * Multiply by A
226 *
227  DO 80 j = n, 2, -1
228  CALL zhpmv( 'Lower', n, -cone, a, work( 1, j-1 ), 1, czero,
229  $ work( 1, j ), 1 )
230  80 CONTINUE
231  CALL zhpmv( 'Lower', n, -cone, a, ainv( 1 ), 1, czero,
232  $ work( 1, 1 ), 1 )
233 *
234  END IF
235 *
236 * Add the identity matrix to WORK .
237 *
238  DO 90 i = 1, n
239  work( i, i ) = work( i, i ) + cone
240  90 CONTINUE
241 *
242 * Compute norm(I - A*AINV) / (N * norm(A) * norm(AINV) * EPS)
243 *
244  resid = zlange( '1', n, n, work, ldwork, rwork )
245 *
246  resid = ( ( resid*rcond ) / eps ) / dble( n )
247 *
248  RETURN
249 *
250 * End of ZPPT03
251 *
252  END
subroutine zcopy(N, ZX, INCX, ZY, INCY)
ZCOPY
Definition: zcopy.f:52
subroutine zppt03(UPLO, N, A, AINV, WORK, LDWORK, RWORK, RCOND, RESID)
ZPPT03
Definition: zppt03.f:112
subroutine zhpmv(UPLO, N, ALPHA, AP, X, INCX, BETA, Y, INCY)
ZHPMV
Definition: zhpmv.f:151