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

CGET52

Purpose:
 CGET52  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.

 CGET52 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, CGET52 does
          nothing.  It must be at least zero.
[in]A
          A is COMPLEX 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 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 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 array, dimension (N)
          The values a(i) as described above, which, along with b(i),
          define the generalized eigenvalues.
[in]BETA
          BETA is COMPLEX array, dimension (N)
          The values b(i) as described above, which, along with a(i),
          define the generalized eigenvalues.
[out]WORK
          WORK is COMPLEX array, dimension (N**2)
[out]RWORK
          RWORK is REAL array, dimension (N)
[out]RESULT
          RESULT is REAL 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 163 of file cget52.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: