LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
zspt03.f
Go to the documentation of this file.
1 *> \brief \b ZSPT03
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 ZSPT03( UPLO, N, A, AINV, WORK, LDW, RWORK, RCOND,
12 * RESID )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER UPLO
16 * INTEGER LDW, N
17 * DOUBLE PRECISION RCOND, RESID
18 * ..
19 * .. Array Arguments ..
20 * DOUBLE PRECISION RWORK( * )
21 * COMPLEX*16 A( * ), AINV( * ), WORK( LDW, * )
22 * ..
23 *
24 *
25 *> \par Purpose:
26 * =============
27 *>
28 *> \verbatim
29 *>
30 *> ZSPT03 computes the residual for a complex symmetric packed matrix
31 *> times its 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 *> complex symmetric 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 complex symmetric 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 (symmetric) 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 (LDW,N)
71 *> \endverbatim
72 *>
73 *> \param[in] LDW
74 *> \verbatim
75 *> LDW is INTEGER
76 *> The leading dimension of the array WORK. LDW >= 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 zspt03( UPLO, N, A, AINV, WORK, LDW, 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 LDW, N
121  DOUBLE PRECISION RCOND, RESID
122 * ..
123 * .. Array Arguments ..
124  DOUBLE PRECISION RWORK( * )
125  COMPLEX*16 A( * ), AINV( * ), WORK( ldw, * )
126 * ..
127 *
128 * =====================================================================
129 *
130 * .. Parameters ..
131  DOUBLE PRECISION ZERO, ONE
132  parameter ( zero = 0.0d+0, one = 1.0d+0 )
133 * ..
134 * .. Local Scalars ..
135  INTEGER I, ICOL, J, JCOL, K, KCOL, NALL
136  DOUBLE PRECISION AINVNM, ANORM, EPS
137  COMPLEX*16 T
138 * ..
139 * .. External Functions ..
140  LOGICAL LSAME
141  DOUBLE PRECISION DLAMCH, ZLANGE, ZLANSP
142  COMPLEX*16 ZDOTU
143  EXTERNAL lsame, dlamch, zlange, zlansp, zdotu
144 * ..
145 * .. Intrinsic Functions ..
146  INTRINSIC dble
147 * ..
148 * .. Executable Statements ..
149 *
150 * Quick exit if N = 0.
151 *
152  IF( n.LE.0 ) THEN
153  rcond = one
154  resid = zero
155  RETURN
156  END IF
157 *
158 * Exit with RESID = 1/EPS if ANORM = 0 or AINVNM = 0.
159 *
160  eps = dlamch( 'Epsilon' )
161  anorm = zlansp( '1', uplo, n, a, rwork )
162  ainvnm = zlansp( '1', uplo, n, ainv, rwork )
163  IF( anorm.LE.zero .OR. ainvnm.LE.zero ) THEN
164  rcond = zero
165  resid = one / eps
166  RETURN
167  END IF
168  rcond = ( one / anorm ) / ainvnm
169 *
170 * Case where both A and AINV are upper triangular:
171 * Each element of - A * AINV is computed by taking the dot product
172 * of a row of A with a column of AINV.
173 *
174  IF( lsame( uplo, 'U' ) ) THEN
175  DO 70 i = 1, n
176  icol = ( ( i-1 )*i ) / 2 + 1
177 *
178 * Code when J <= I
179 *
180  DO 30 j = 1, i
181  jcol = ( ( j-1 )*j ) / 2 + 1
182  t = zdotu( j, a( icol ), 1, ainv( jcol ), 1 )
183  jcol = jcol + 2*j - 1
184  kcol = icol - 1
185  DO 10 k = j + 1, i
186  t = t + a( kcol+k )*ainv( jcol )
187  jcol = jcol + k
188  10 CONTINUE
189  kcol = kcol + 2*i
190  DO 20 k = i + 1, n
191  t = t + a( kcol )*ainv( jcol )
192  kcol = kcol + k
193  jcol = jcol + k
194  20 CONTINUE
195  work( i, j ) = -t
196  30 CONTINUE
197 *
198 * Code when J > I
199 *
200  DO 60 j = i + 1, n
201  jcol = ( ( j-1 )*j ) / 2 + 1
202  t = zdotu( i, a( icol ), 1, ainv( jcol ), 1 )
203  jcol = jcol - 1
204  kcol = icol + 2*i - 1
205  DO 40 k = i + 1, j
206  t = t + a( kcol )*ainv( jcol+k )
207  kcol = kcol + k
208  40 CONTINUE
209  jcol = jcol + 2*j
210  DO 50 k = j + 1, n
211  t = t + a( kcol )*ainv( jcol )
212  kcol = kcol + k
213  jcol = jcol + k
214  50 CONTINUE
215  work( i, j ) = -t
216  60 CONTINUE
217  70 CONTINUE
218  ELSE
219 *
220 * Case where both A and AINV are lower triangular
221 *
222  nall = ( n*( n+1 ) ) / 2
223  DO 140 i = 1, n
224 *
225 * Code when J <= I
226 *
227  icol = nall - ( ( n-i+1 )*( n-i+2 ) ) / 2 + 1
228  DO 100 j = 1, i
229  jcol = nall - ( ( n-j )*( n-j+1 ) ) / 2 - ( n-i )
230  t = zdotu( n-i+1, a( icol ), 1, ainv( jcol ), 1 )
231  kcol = i
232  jcol = j
233  DO 80 k = 1, j - 1
234  t = t + a( kcol )*ainv( jcol )
235  jcol = jcol + n - k
236  kcol = kcol + n - k
237  80 CONTINUE
238  jcol = jcol - j
239  DO 90 k = j, i - 1
240  t = t + a( kcol )*ainv( jcol+k )
241  kcol = kcol + n - k
242  90 CONTINUE
243  work( i, j ) = -t
244  100 CONTINUE
245 *
246 * Code when J > I
247 *
248  icol = nall - ( ( n-i )*( n-i+1 ) ) / 2
249  DO 130 j = i + 1, n
250  jcol = nall - ( ( n-j+1 )*( n-j+2 ) ) / 2 + 1
251  t = zdotu( n-j+1, a( icol-n+j ), 1, ainv( jcol ), 1 )
252  kcol = i
253  jcol = j
254  DO 110 k = 1, i - 1
255  t = t + a( kcol )*ainv( jcol )
256  jcol = jcol + n - k
257  kcol = kcol + n - k
258  110 CONTINUE
259  kcol = kcol - i
260  DO 120 k = i, j - 1
261  t = t + a( kcol+k )*ainv( jcol )
262  jcol = jcol + n - k
263  120 CONTINUE
264  work( i, j ) = -t
265  130 CONTINUE
266  140 CONTINUE
267  END IF
268 *
269 * Add the identity matrix to WORK .
270 *
271  DO 150 i = 1, n
272  work( i, i ) = work( i, i ) + one
273  150 CONTINUE
274 *
275 * Compute norm(I - A*AINV) / (N * norm(A) * norm(AINV) * EPS)
276 *
277  resid = zlange( '1', n, n, work, ldw, rwork )
278 *
279  resid = ( ( resid*rcond ) / eps ) / dble( n )
280 *
281  RETURN
282 *
283 * End of ZSPT03
284 *
285  END
subroutine zspt03(UPLO, N, A, AINV, WORK, LDW, RWORK, RCOND, RESID)
ZSPT03
Definition: zspt03.f:112