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

◆ cget52()

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 
!> of its elements is 1, where in this case, 
!> of a complex value x is  |Re(x)| + |Im(x)| ; let us call this
!> maximum  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.

Definition at line 159 of file cget52.f.

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