LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ zget52()

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.

Definition at line 160 of file zget52.f.

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