LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zget52 ( logical  LEFT,
integer  N,
complex*16, dimension( lda, * )  A,
integer  LDA,
complex*16, dimension( ldb, * )  B,
integer  LDB,
complex*16, dimension( lde, * )  E,
integer  LDE,
complex*16, dimension( * )  ALPHA,
complex*16, dimension( * )  BETA,
complex*16, dimension( * )  WORK,
double precision, dimension( * )  RWORK,
double precision, dimension( 2 )  RESULT 
)

ZGET52

Purpose:
 ZGET52  does an eigenvector check for the generalized eigenvalue
 problem.

 The basic test for right eigenvectors is:

                           | b(i) A E(i) -  a(i) B E(i) |
         RESULT(1) = max   -------------------------------
                      i    n ulp max( |b(i) A|, |a(i) B| )

 using the 1-norm.  Here, a(i)/b(i) = w is the i-th generalized
 eigenvalue of A - w B, or, equivalently, b(i)/a(i) = m is the i-th
 generalized eigenvalue of m A - B.

                         H   H  _      _
 For left eigenvectors, A , B , a, and b  are used.

 ZGET52 also tests the normalization of E.  Each eigenvector is
 supposed to be normalized so that the maximum "absolute value"
 of its elements is 1, where in this case, "absolute value"
 of a complex value x is  |Re(x)| + |Im(x)| ; let us call this
 maximum "absolute value" norm of a vector v  M(v).  
 If a(i)=b(i)=0, then the eigenvector is set to be the jth coordinate
 vector. The normalization test is:

         RESULT(2) =      max       | M(v(i)) - 1 | / ( n ulp )
                    eigenvectors v(i)
Parameters
[in]LEFT
          LEFT is LOGICAL
          =.TRUE.:  The eigenvectors in the columns of E are assumed
                    to be *left* eigenvectors.
          =.FALSE.: The eigenvectors in the columns of E are assumed
                    to be *right* eigenvectors.
[in]N
          N is INTEGER
          The size of the matrices.  If it is zero, ZGET52 does
          nothing.  It must be at least zero.
[in]A
          A is COMPLEX*16 array, dimension (LDA, N)
          The matrix A.
[in]LDA
          LDA is INTEGER
          The leading dimension of A.  It must be at least 1
          and at least N.
[in]B
          B is COMPLEX*16 array, dimension (LDB, N)
          The matrix B.
[in]LDB
          LDB is INTEGER
          The leading dimension of B.  It must be at least 1
          and at least N.
[in]E
          E is COMPLEX*16 array, dimension (LDE, N)
          The matrix of eigenvectors.  It must be O( 1 ).
[in]LDE
          LDE is INTEGER
          The leading dimension of E.  It must be at least 1 and at
          least N.
[in]ALPHA
          ALPHA is COMPLEX*16 array, dimension (N)
          The values a(i) as described above, which, along with b(i),
          define the generalized eigenvalues.
[in]BETA
          BETA is COMPLEX*16 array, dimension (N)
          The values b(i) as described above, which, along with a(i),
          define the generalized eigenvalues.
[out]WORK
          WORK is COMPLEX*16 array, dimension (N**2)
[out]RWORK
          RWORK is DOUBLE PRECISION array, dimension (N)
[out]RESULT
          RESULT is DOUBLE PRECISION array, dimension (2)
          The values computed by the test described above.  If A E or
          B E is likely to overflow, then RESULT(1:2) is set to
          10 / ulp.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011

Definition at line 164 of file zget52.f.

164 *
165 * -- LAPACK test routine (version 3.4.0) --
166 * -- LAPACK is a software package provided by Univ. of Tennessee, --
167 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
168 * November 2011
169 *
170 * .. Scalar Arguments ..
171  LOGICAL left
172  INTEGER lda, ldb, lde, n
173 * ..
174 * .. Array Arguments ..
175  DOUBLE PRECISION result( 2 ), rwork( * )
176  COMPLEX*16 a( lda, * ), alpha( * ), b( ldb, * ),
177  $ beta( * ), e( lde, * ), work( * )
178 * ..
179 *
180 * =====================================================================
181 *
182 * .. Parameters ..
183  DOUBLE PRECISION zero, one
184  parameter ( zero = 0.0d+0, one = 1.0d+0 )
185  COMPLEX*16 czero, cone
186  parameter ( czero = ( 0.0d+0, 0.0d+0 ),
187  $ cone = ( 1.0d+0, 0.0d+0 ) )
188 * ..
189 * .. Local Scalars ..
190  CHARACTER normab, trans
191  INTEGER j, jvec
192  DOUBLE PRECISION abmax, alfmax, anorm, betmax, bnorm, enorm,
193  $ enrmer, errnrm, safmax, safmin, scale, temp1,
194  $ ulp
195  COMPLEX*16 acoeff, alphai, bcoeff, betai, x
196 * ..
197 * .. External Functions ..
198  DOUBLE PRECISION dlamch, zlange
199  EXTERNAL dlamch, zlange
200 * ..
201 * .. External Subroutines ..
202  EXTERNAL zgemv
203 * ..
204 * .. Intrinsic Functions ..
205  INTRINSIC abs, dble, dconjg, dimag, max
206 * ..
207 * .. Statement Functions ..
208  DOUBLE PRECISION abs1
209 * ..
210 * .. Statement Function definitions ..
211  abs1( x ) = abs( dble( x ) ) + abs( dimag( x ) )
212 * ..
213 * .. Executable Statements ..
214 *
215  result( 1 ) = zero
216  result( 2 ) = zero
217  IF( n.LE.0 )
218  $ RETURN
219 *
220  safmin = dlamch( 'Safe minimum' )
221  safmax = one / safmin
222  ulp = dlamch( 'Epsilon' )*dlamch( 'Base' )
223 *
224  IF( left ) THEN
225  trans = 'C'
226  normab = 'I'
227  ELSE
228  trans = 'N'
229  normab = 'O'
230  END IF
231 *
232 * Norm of A, B, and E:
233 *
234  anorm = max( zlange( normab, n, n, a, lda, rwork ), safmin )
235  bnorm = max( zlange( normab, n, n, b, ldb, rwork ), safmin )
236  enorm = max( zlange( 'O', n, n, e, lde, rwork ), ulp )
237  alfmax = safmax / max( one, bnorm )
238  betmax = safmax / max( one, anorm )
239 *
240 * Compute error matrix.
241 * Column i = ( b(i) A - a(i) B ) E(i) / max( |a(i) B| |b(i) A| )
242 *
243  DO 10 jvec = 1, n
244  alphai = alpha( jvec )
245  betai = beta( jvec )
246  abmax = max( abs1( alphai ), abs1( betai ) )
247  IF( abs1( alphai ).GT.alfmax .OR. abs1( betai ).GT.betmax .OR.
248  $ abmax.LT.one ) THEN
249  scale = one / max( abmax, safmin )
250  alphai = scale*alphai
251  betai = scale*betai
252  END IF
253  scale = one / max( abs1( alphai )*bnorm, abs1( betai )*anorm,
254  $ safmin )
255  acoeff = scale*betai
256  bcoeff = scale*alphai
257  IF( left ) THEN
258  acoeff = dconjg( acoeff )
259  bcoeff = dconjg( bcoeff )
260  END IF
261  CALL zgemv( trans, n, n, acoeff, a, lda, e( 1, jvec ), 1,
262  $ czero, work( n*( jvec-1 )+1 ), 1 )
263  CALL zgemv( trans, n, n, -bcoeff, b, lda, e( 1, jvec ), 1,
264  $ cone, work( n*( jvec-1 )+1 ), 1 )
265  10 CONTINUE
266 *
267  errnrm = zlange( 'One', n, n, work, n, rwork ) / enorm
268 *
269 * Compute RESULT(1)
270 *
271  result( 1 ) = errnrm / ulp
272 *
273 * Normalization of E:
274 *
275  enrmer = zero
276  DO 30 jvec = 1, n
277  temp1 = zero
278  DO 20 j = 1, n
279  temp1 = max( temp1, abs1( e( j, jvec ) ) )
280  20 CONTINUE
281  enrmer = max( enrmer, temp1-one )
282  30 CONTINUE
283 *
284 * Compute RESULT(2) : the normalization error in E.
285 *
286  result( 2 ) = enrmer / ( dble( n )*ulp )
287 *
288  RETURN
289 *
290 * End of ZGET52
291 *
double precision function dlamch(CMACH)
DLAMCH
Definition: dlamch.f:65
subroutine zgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
ZGEMV
Definition: zgemv.f:160
logical function lde(RI, RJ, LR)
Definition: dblat2.f:2945
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

Here is the call graph for this function:

Here is the caller graph for this function: