SUBROUTINE SGET52( LEFT, N, A, LDA, B, LDB, E, LDE, ALPHAR, $ ALPHAI, BETA, WORK, RESULT ) * * -- LAPACK test routine (version 3.1) -- * Univ. of Tennessee, Univ. of California Berkeley and NAG Ltd.. * November 2006 * * .. Scalar Arguments .. LOGICAL LEFT INTEGER LDA, LDB, LDE, N * .. * .. Array Arguments .. REAL A( LDA, * ), ALPHAI( * ), ALPHAR( * ), $ B( LDB, * ), BETA( * ), E( LDE, * ), $ RESULT( 2 ), WORK( * ) * .. * * Purpose * ======= * * SGET52 does an eigenvector check for the generalized eigenvalue * problem. * * The basic test for right eigenvectors is: * * | b(j) A E(j) - a(j) B E(j) | * RESULT(1) = max ------------------------------- * j n ulp max( |b(j) A|, |a(j) B| ) * * using the 1-norm. Here, a(j)/b(j) = w is the j-th generalized * eigenvalue of A - w B, or, equivalently, b(j)/a(j) = m is the j-th * generalized eigenvalue of m A - B. * * For real eigenvalues, the test is straightforward. For complex * eigenvalues, E(j) and a(j) are complex, represented by * Er(j) + i*Ei(j) and ar(j) + i*ai(j), resp., so the test for that * eigenvector becomes * * max( |Wr|, |Wi| ) * -------------------------------------------- * n ulp max( |b(j) A|, (|ar(j)|+|ai(j)|) |B| ) * * where * * Wr = b(j) A Er(j) - ar(j) B Er(j) + ai(j) B Ei(j) * * Wi = b(j) A Ei(j) - ai(j) B Er(j) - ar(j) B Ei(j) * * T T _ * For left eigenvectors, A , B , a, and b are used. * * SGET52 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(j)=b(j)=0, then the eigenvector is set to be the jth coordinate * vector. The normalization test is: * * RESULT(2) = max | M(v(j)) - 1 | / ( n ulp ) * eigenvectors v(j) * * Arguments * ========= * * LEFT (input) 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. * * N (input) INTEGER * The size of the matrices. If it is zero, SGET52 does * nothing. It must be at least zero. * * A (input) REAL array, dimension (LDA, N) * The matrix A. * * LDA (input) INTEGER * The leading dimension of A. It must be at least 1 * and at least N. * * B (input) REAL array, dimension (LDB, N) * The matrix B. * * LDB (input) INTEGER * The leading dimension of B. It must be at least 1 * and at least N. * * E (input) REAL array, dimension (LDE, N) * The matrix of eigenvectors. It must be O( 1 ). Complex * eigenvalues and eigenvectors always come in pairs, the * eigenvalue and its conjugate being stored in adjacent * elements of ALPHAR, ALPHAI, and BETA. Thus, if a(j)/b(j) * and a(j+1)/b(j+1) are a complex conjugate pair of * generalized eigenvalues, then E(,j) contains the real part * of the eigenvector and E(,j+1) contains the imaginary part. * Note that whether E(,j) is a real eigenvector or part of a * complex one is specified by whether ALPHAI(j) is zero or not. * * LDE (input) INTEGER * The leading dimension of E. It must be at least 1 and at * least N. * * ALPHAR (input) REAL array, dimension (N) * The real parts of the values a(j) as described above, which, * along with b(j), define the generalized eigenvalues. * Complex eigenvalues always come in complex conjugate pairs * a(j)/b(j) and a(j+1)/b(j+1), which are stored in adjacent * elements in ALPHAR, ALPHAI, and BETA. Thus, if the j-th * and (j+1)-st eigenvalues form a pair, ALPHAR(j+1)/BETA(j+1) * is assumed to be equal to ALPHAR(j)/BETA(j). * * ALPHAI (input) REAL array, dimension (N) * The imaginary parts of the values a(j) as described above, * which, along with b(j), define the generalized eigenvalues. * If ALPHAI(j)=0, then the eigenvalue is real, otherwise it * is part of a complex conjugate pair. Complex eigenvalues * always come in complex conjugate pairs a(j)/b(j) and * a(j+1)/b(j+1), which are stored in adjacent elements in * ALPHAR, ALPHAI, and BETA. Thus, if the j-th and (j+1)-st * eigenvalues form a pair, ALPHAI(j+1)/BETA(j+1) is assumed to * be equal to -ALPHAI(j)/BETA(j). Also, nonzero values in * ALPHAI are assumed to always come in adjacent pairs. * * BETA (input) REAL array, dimension (N) * The values b(j) as described above, which, along with a(j), * define the generalized eigenvalues. * * WORK (workspace) REAL array, dimension (N**2+N) * * RESULT (output) 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. * * ===================================================================== * * .. Parameters .. REAL ZERO, ONE, TEN PARAMETER ( ZERO = 0.0, ONE = 1.0, TEN = 10.0 ) * .. * .. Local Scalars .. LOGICAL ILCPLX CHARACTER NORMAB, TRANS INTEGER J, JVEC REAL ABMAX, ACOEF, ALFMAX, ANORM, BCOEFI, BCOEFR, $ BETMAX, BNORM, ENORM, ENRMER, ERRNRM, SAFMAX, $ SAFMIN, SALFI, SALFR, SBETA, SCALE, TEMP1, ULP * .. * .. External Functions .. REAL SLAMCH, SLANGE EXTERNAL SLAMCH, SLANGE * .. * .. External Subroutines .. EXTERNAL SGEMV * .. * .. Intrinsic Functions .. INTRINSIC ABS, MAX, REAL * .. * .. Executable Statements .. * RESULT( 1 ) = ZERO RESULT( 2 ) = ZERO IF( N.LE.0 ) $ RETURN * SAFMIN = SLAMCH( 'Safe minimum' ) SAFMAX = ONE / SAFMIN ULP = SLAMCH( 'Epsilon' )*SLAMCH( 'Base' ) * IF( LEFT ) THEN TRANS = 'T' NORMAB = 'I' ELSE TRANS = 'N' NORMAB = 'O' END IF * * Norm of A, B, and E: * ANORM = MAX( SLANGE( NORMAB, N, N, A, LDA, WORK ), SAFMIN ) BNORM = MAX( SLANGE( NORMAB, N, N, B, LDB, WORK ), SAFMIN ) ENORM = MAX( SLANGE( 'O', N, N, E, LDE, WORK ), ULP ) ALFMAX = SAFMAX / MAX( ONE, BNORM ) BETMAX = SAFMAX / MAX( ONE, ANORM ) * * Compute error matrix. * Column i = ( b(i) A - a(i) B ) E(i) / max( |a(i) B| |b(i) A| ) * ILCPLX = .FALSE. DO 10 JVEC = 1, N IF( ILCPLX ) THEN * * 2nd Eigenvalue/-vector of pair -- do nothing * ILCPLX = .FALSE. ELSE SALFR = ALPHAR( JVEC ) SALFI = ALPHAI( JVEC ) SBETA = BETA( JVEC ) IF( SALFI.EQ.ZERO ) THEN * * Real eigenvalue and -vector * ABMAX = MAX( ABS( SALFR ), ABS( SBETA ) ) IF( ABS( SALFR ).GT.ALFMAX .OR. ABS( SBETA ).GT. $ BETMAX .OR. ABMAX.LT.ONE ) THEN SCALE = ONE / MAX( ABMAX, SAFMIN ) SALFR = SCALE*SALFR SBETA = SCALE*SBETA END IF SCALE = ONE / MAX( ABS( SALFR )*BNORM, $ ABS( SBETA )*ANORM, SAFMIN ) ACOEF = SCALE*SBETA BCOEFR = SCALE*SALFR CALL SGEMV( TRANS, N, N, ACOEF, A, LDA, E( 1, JVEC ), 1, $ ZERO, WORK( N*( JVEC-1 )+1 ), 1 ) CALL SGEMV( TRANS, N, N, -BCOEFR, B, LDA, E( 1, JVEC ), $ 1, ONE, WORK( N*( JVEC-1 )+1 ), 1 ) ELSE * * Complex conjugate pair * ILCPLX = .TRUE. IF( JVEC.EQ.N ) THEN RESULT( 1 ) = TEN / ULP RETURN END IF ABMAX = MAX( ABS( SALFR )+ABS( SALFI ), ABS( SBETA ) ) IF( ABS( SALFR )+ABS( SALFI ).GT.ALFMAX .OR. $ ABS( SBETA ).GT.BETMAX .OR. ABMAX.LT.ONE ) THEN SCALE = ONE / MAX( ABMAX, SAFMIN ) SALFR = SCALE*SALFR SALFI = SCALE*SALFI SBETA = SCALE*SBETA END IF SCALE = ONE / MAX( ( ABS( SALFR )+ABS( SALFI ) )*BNORM, $ ABS( SBETA )*ANORM, SAFMIN ) ACOEF = SCALE*SBETA BCOEFR = SCALE*SALFR BCOEFI = SCALE*SALFI IF( LEFT ) THEN BCOEFI = -BCOEFI END IF * CALL SGEMV( TRANS, N, N, ACOEF, A, LDA, E( 1, JVEC ), 1, $ ZERO, WORK( N*( JVEC-1 )+1 ), 1 ) CALL SGEMV( TRANS, N, N, -BCOEFR, B, LDA, E( 1, JVEC ), $ 1, ONE, WORK( N*( JVEC-1 )+1 ), 1 ) CALL SGEMV( TRANS, N, N, BCOEFI, B, LDA, E( 1, JVEC+1 ), $ 1, ONE, WORK( N*( JVEC-1 )+1 ), 1 ) * CALL SGEMV( TRANS, N, N, ACOEF, A, LDA, E( 1, JVEC+1 ), $ 1, ZERO, WORK( N*JVEC+1 ), 1 ) CALL SGEMV( TRANS, N, N, -BCOEFI, B, LDA, E( 1, JVEC ), $ 1, ONE, WORK( N*JVEC+1 ), 1 ) CALL SGEMV( TRANS, N, N, -BCOEFR, B, LDA, E( 1, JVEC+1 ), $ 1, ONE, WORK( N*JVEC+1 ), 1 ) END IF END IF 10 CONTINUE * ERRNRM = SLANGE( 'One', N, N, WORK, N, WORK( N**2+1 ) ) / ENORM * * Compute RESULT(1) * RESULT( 1 ) = ERRNRM / ULP * * Normalization of E: * ENRMER = ZERO ILCPLX = .FALSE. DO 40 JVEC = 1, N IF( ILCPLX ) THEN ILCPLX = .FALSE. ELSE TEMP1 = ZERO IF( ALPHAI( JVEC ).EQ.ZERO ) THEN DO 20 J = 1, N TEMP1 = MAX( TEMP1, ABS( E( J, JVEC ) ) ) 20 CONTINUE ENRMER = MAX( ENRMER, TEMP1-ONE ) ELSE ILCPLX = .TRUE. DO 30 J = 1, N TEMP1 = MAX( TEMP1, ABS( E( J, JVEC ) )+ $ ABS( E( J, JVEC+1 ) ) ) 30 CONTINUE ENRMER = MAX( ENRMER, TEMP1-ONE ) END IF END IF 40 CONTINUE * * Compute RESULT(2) : the normalization error in E. * RESULT( 2 ) = ENRMER / ( REAL( N )*ULP ) * RETURN * * End of SGET52 * END