LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zspt03 ( character  UPLO,
integer  N,
complex*16, dimension( * )  A,
complex*16, dimension( * )  AINV,
complex*16, dimension( ldw, * )  WORK,
integer  LDW,
double precision, dimension( * )  RWORK,
double precision  RCOND,
double precision  RESID 
)

ZSPT03

Purpose:
 ZSPT03 computes the residual for a complex symmetric packed matrix
 times its inverse:
    norm( I - A*AINV ) / ( N * norm(A) * norm(AINV) * EPS ),
 where EPS is the machine epsilon.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the upper or lower triangular part of the
          complex symmetric matrix A is stored:
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]N
          N is INTEGER
          The number of rows and columns of the matrix A.  N >= 0.
[in]A
          A is COMPLEX*16 array, dimension (N*(N+1)/2)
          The original complex symmetric matrix A, stored as a packed
          triangular matrix.
[in]AINV
          AINV is COMPLEX*16 array, dimension (N*(N+1)/2)
          The (symmetric) inverse of the matrix A, stored as a packed
          triangular matrix.
[out]WORK
          WORK is COMPLEX*16 array, dimension (LDW,N)
[in]LDW
          LDW is INTEGER
          The leading dimension of the array WORK.  LDW >= max(1,N).
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (N)
[out]RCOND
          RCOND is DOUBLE PRECISION
          The reciprocal of the condition number of A, computed as
          ( 1/norm(A) ) / norm(AINV).
[out]RESID
          RESID is DOUBLE PRECISION
          norm(I - A*AINV) / ( N * norm(A) * norm(AINV) * EPS )
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 112 of file zspt03.f.

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 *
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
complex *16 function zdotu(N, ZX, INCX, ZY, INCY)
ZDOTU
Definition: zdotu.f:54
double precision function zlange(NORM, M, N, A, LDA, WORK)
ZLANGE returns the value of the 1-norm, Frobenius norm, infinity-norm, or the largest absolute value ...
Definition: zlange.f:117
double precision function zlansp(NORM, UPLO, N, AP, WORK)
ZLANSP returns the value of the 1-norm, or the Frobenius norm, or the infinity norm, or the element of largest absolute value of a symmetric matrix supplied in packed form.
Definition: zlansp.f:117
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the caller graph for this function: