You can not select more than 25 topics Topics must start with a chinese character,a letter or number, can include dashes ('-') and can be up to 35 characters long.

dget52.f 13 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383
  1. *> \brief \b DGET52
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. * Definition:
  9. * ===========
  10. *
  11. * SUBROUTINE DGET52( LEFT, N, A, LDA, B, LDB, E, LDE, ALPHAR,
  12. * ALPHAI, BETA, WORK, RESULT )
  13. *
  14. * .. Scalar Arguments ..
  15. * LOGICAL LEFT
  16. * INTEGER LDA, LDB, LDE, N
  17. * ..
  18. * .. Array Arguments ..
  19. * DOUBLE PRECISION A( LDA, * ), ALPHAI( * ), ALPHAR( * ),
  20. * $ B( LDB, * ), BETA( * ), E( LDE, * ),
  21. * $ RESULT( 2 ), WORK( * )
  22. * ..
  23. *
  24. *
  25. *> \par Purpose:
  26. * =============
  27. *>
  28. *> \verbatim
  29. *>
  30. *> DGET52 does an eigenvector check for the generalized eigenvalue
  31. *> problem.
  32. *>
  33. *> The basic test for right eigenvectors is:
  34. *>
  35. *> | b(j) A E(j) - a(j) B E(j) |
  36. *> RESULT(1) = max -------------------------------
  37. *> j n ulp max( |b(j) A|, |a(j) B| )
  38. *>
  39. *> using the 1-norm. Here, a(j)/b(j) = w is the j-th generalized
  40. *> eigenvalue of A - w B, or, equivalently, b(j)/a(j) = m is the j-th
  41. *> generalized eigenvalue of m A - B.
  42. *>
  43. *> For real eigenvalues, the test is straightforward. For complex
  44. *> eigenvalues, E(j) and a(j) are complex, represented by
  45. *> Er(j) + i*Ei(j) and ar(j) + i*ai(j), resp., so the test for that
  46. *> eigenvector becomes
  47. *>
  48. *> max( |Wr|, |Wi| )
  49. *> --------------------------------------------
  50. *> n ulp max( |b(j) A|, (|ar(j)|+|ai(j)|) |B| )
  51. *>
  52. *> where
  53. *>
  54. *> Wr = b(j) A Er(j) - ar(j) B Er(j) + ai(j) B Ei(j)
  55. *>
  56. *> Wi = b(j) A Ei(j) - ai(j) B Er(j) - ar(j) B Ei(j)
  57. *>
  58. *> T T _
  59. *> For left eigenvectors, A , B , a, and b are used.
  60. *>
  61. *> DGET52 also tests the normalization of E. Each eigenvector is
  62. *> supposed to be normalized so that the maximum "absolute value"
  63. *> of its elements is 1, where in this case, "absolute value"
  64. *> of a complex value x is |Re(x)| + |Im(x)| ; let us call this
  65. *> maximum "absolute value" norm of a vector v M(v).
  66. *> if a(j)=b(j)=0, then the eigenvector is set to be the jth coordinate
  67. *> vector. The normalization test is:
  68. *>
  69. *> RESULT(2) = max | M(v(j)) - 1 | / ( n ulp )
  70. *> eigenvectors v(j)
  71. *> \endverbatim
  72. *
  73. * Arguments:
  74. * ==========
  75. *
  76. *> \param[in] LEFT
  77. *> \verbatim
  78. *> LEFT is LOGICAL
  79. *> =.TRUE.: The eigenvectors in the columns of E are assumed
  80. *> to be *left* eigenvectors.
  81. *> =.FALSE.: The eigenvectors in the columns of E are assumed
  82. *> to be *right* eigenvectors.
  83. *> \endverbatim
  84. *>
  85. *> \param[in] N
  86. *> \verbatim
  87. *> N is INTEGER
  88. *> The size of the matrices. If it is zero, DGET52 does
  89. *> nothing. It must be at least zero.
  90. *> \endverbatim
  91. *>
  92. *> \param[in] A
  93. *> \verbatim
  94. *> A is DOUBLE PRECISION array, dimension (LDA, N)
  95. *> The matrix A.
  96. *> \endverbatim
  97. *>
  98. *> \param[in] LDA
  99. *> \verbatim
  100. *> LDA is INTEGER
  101. *> The leading dimension of A. It must be at least 1
  102. *> and at least N.
  103. *> \endverbatim
  104. *>
  105. *> \param[in] B
  106. *> \verbatim
  107. *> B is DOUBLE PRECISION array, dimension (LDB, N)
  108. *> The matrix B.
  109. *> \endverbatim
  110. *>
  111. *> \param[in] LDB
  112. *> \verbatim
  113. *> LDB is INTEGER
  114. *> The leading dimension of B. It must be at least 1
  115. *> and at least N.
  116. *> \endverbatim
  117. *>
  118. *> \param[in] E
  119. *> \verbatim
  120. *> E is DOUBLE PRECISION array, dimension (LDE, N)
  121. *> The matrix of eigenvectors. It must be O( 1 ). Complex
  122. *> eigenvalues and eigenvectors always come in pairs, the
  123. *> eigenvalue and its conjugate being stored in adjacent
  124. *> elements of ALPHAR, ALPHAI, and BETA. Thus, if a(j)/b(j)
  125. *> and a(j+1)/b(j+1) are a complex conjugate pair of
  126. *> generalized eigenvalues, then E(,j) contains the real part
  127. *> of the eigenvector and E(,j+1) contains the imaginary part.
  128. *> Note that whether E(,j) is a real eigenvector or part of a
  129. *> complex one is specified by whether ALPHAI(j) is zero or not.
  130. *> \endverbatim
  131. *>
  132. *> \param[in] LDE
  133. *> \verbatim
  134. *> LDE is INTEGER
  135. *> The leading dimension of E. It must be at least 1 and at
  136. *> least N.
  137. *> \endverbatim
  138. *>
  139. *> \param[in] ALPHAR
  140. *> \verbatim
  141. *> ALPHAR is DOUBLE PRECISION array, dimension (N)
  142. *> The real parts of the values a(j) as described above, which,
  143. *> along with b(j), define the generalized eigenvalues.
  144. *> Complex eigenvalues always come in complex conjugate pairs
  145. *> a(j)/b(j) and a(j+1)/b(j+1), which are stored in adjacent
  146. *> elements in ALPHAR, ALPHAI, and BETA. Thus, if the j-th
  147. *> and (j+1)-st eigenvalues form a pair, ALPHAR(j+1)/BETA(j+1)
  148. *> is assumed to be equal to ALPHAR(j)/BETA(j).
  149. *> \endverbatim
  150. *>
  151. *> \param[in] ALPHAI
  152. *> \verbatim
  153. *> ALPHAI is DOUBLE PRECISION array, dimension (N)
  154. *> The imaginary parts of the values a(j) as described above,
  155. *> which, along with b(j), define the generalized eigenvalues.
  156. *> If ALPHAI(j)=0, then the eigenvalue is real, otherwise it
  157. *> is part of a complex conjugate pair. Complex eigenvalues
  158. *> always come in complex conjugate pairs a(j)/b(j) and
  159. *> a(j+1)/b(j+1), which are stored in adjacent elements in
  160. *> ALPHAR, ALPHAI, and BETA. Thus, if the j-th and (j+1)-st
  161. *> eigenvalues form a pair, ALPHAI(j+1)/BETA(j+1) is assumed to
  162. *> be equal to -ALPHAI(j)/BETA(j). Also, nonzero values in
  163. *> ALPHAI are assumed to always come in adjacent pairs.
  164. *> \endverbatim
  165. *>
  166. *> \param[in] BETA
  167. *> \verbatim
  168. *> BETA is DOUBLE PRECISION array, dimension (N)
  169. *> The values b(j) as described above, which, along with a(j),
  170. *> define the generalized eigenvalues.
  171. *> \endverbatim
  172. *>
  173. *> \param[out] WORK
  174. *> \verbatim
  175. *> WORK is DOUBLE PRECISION array, dimension (N**2+N)
  176. *> \endverbatim
  177. *>
  178. *> \param[out] RESULT
  179. *> \verbatim
  180. *> RESULT is DOUBLE PRECISION array, dimension (2)
  181. *> The values computed by the test described above. If A E or
  182. *> B E is likely to overflow, then RESULT(1:2) is set to
  183. *> 10 / ulp.
  184. *> \endverbatim
  185. *
  186. * Authors:
  187. * ========
  188. *
  189. *> \author Univ. of Tennessee
  190. *> \author Univ. of California Berkeley
  191. *> \author Univ. of Colorado Denver
  192. *> \author NAG Ltd.
  193. *
  194. *> \date December 2016
  195. *
  196. *> \ingroup double_eig
  197. *
  198. * =====================================================================
  199. SUBROUTINE DGET52( LEFT, N, A, LDA, B, LDB, E, LDE, ALPHAR,
  200. $ ALPHAI, BETA, WORK, RESULT )
  201. *
  202. * -- LAPACK test routine (version 3.7.0) --
  203. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  204. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  205. * December 2016
  206. *
  207. * .. Scalar Arguments ..
  208. LOGICAL LEFT
  209. INTEGER LDA, LDB, LDE, N
  210. * ..
  211. * .. Array Arguments ..
  212. DOUBLE PRECISION A( LDA, * ), ALPHAI( * ), ALPHAR( * ),
  213. $ B( LDB, * ), BETA( * ), E( LDE, * ),
  214. $ RESULT( 2 ), WORK( * )
  215. * ..
  216. *
  217. * =====================================================================
  218. *
  219. * .. Parameters ..
  220. DOUBLE PRECISION ZERO, ONE, TEN
  221. PARAMETER ( ZERO = 0.0D0, ONE = 1.0D0, TEN = 10.0D0 )
  222. * ..
  223. * .. Local Scalars ..
  224. LOGICAL ILCPLX
  225. CHARACTER NORMAB, TRANS
  226. INTEGER J, JVEC
  227. DOUBLE PRECISION ABMAX, ACOEF, ALFMAX, ANORM, BCOEFI, BCOEFR,
  228. $ BETMAX, BNORM, ENORM, ENRMER, ERRNRM, SAFMAX,
  229. $ SAFMIN, SALFI, SALFR, SBETA, SCALE, TEMP1, ULP
  230. * ..
  231. * .. External Functions ..
  232. DOUBLE PRECISION DLAMCH, DLANGE
  233. EXTERNAL DLAMCH, DLANGE
  234. * ..
  235. * .. External Subroutines ..
  236. EXTERNAL DGEMV
  237. * ..
  238. * .. Intrinsic Functions ..
  239. INTRINSIC ABS, DBLE, MAX
  240. * ..
  241. * .. Executable Statements ..
  242. *
  243. RESULT( 1 ) = ZERO
  244. RESULT( 2 ) = ZERO
  245. IF( N.LE.0 )
  246. $ RETURN
  247. *
  248. SAFMIN = DLAMCH( 'Safe minimum' )
  249. SAFMAX = ONE / SAFMIN
  250. ULP = DLAMCH( 'Epsilon' )*DLAMCH( 'Base' )
  251. *
  252. IF( LEFT ) THEN
  253. TRANS = 'T'
  254. NORMAB = 'I'
  255. ELSE
  256. TRANS = 'N'
  257. NORMAB = 'O'
  258. END IF
  259. *
  260. * Norm of A, B, and E:
  261. *
  262. ANORM = MAX( DLANGE( NORMAB, N, N, A, LDA, WORK ), SAFMIN )
  263. BNORM = MAX( DLANGE( NORMAB, N, N, B, LDB, WORK ), SAFMIN )
  264. ENORM = MAX( DLANGE( 'O', N, N, E, LDE, WORK ), ULP )
  265. ALFMAX = SAFMAX / MAX( ONE, BNORM )
  266. BETMAX = SAFMAX / MAX( ONE, ANORM )
  267. *
  268. * Compute error matrix.
  269. * Column i = ( b(i) A - a(i) B ) E(i) / max( |a(i) B| |b(i) A| )
  270. *
  271. ILCPLX = .FALSE.
  272. DO 10 JVEC = 1, N
  273. IF( ILCPLX ) THEN
  274. *
  275. * 2nd Eigenvalue/-vector of pair -- do nothing
  276. *
  277. ILCPLX = .FALSE.
  278. ELSE
  279. SALFR = ALPHAR( JVEC )
  280. SALFI = ALPHAI( JVEC )
  281. SBETA = BETA( JVEC )
  282. IF( SALFI.EQ.ZERO ) THEN
  283. *
  284. * Real eigenvalue and -vector
  285. *
  286. ABMAX = MAX( ABS( SALFR ), ABS( SBETA ) )
  287. IF( ABS( SALFR ).GT.ALFMAX .OR. ABS( SBETA ).GT.
  288. $ BETMAX .OR. ABMAX.LT.ONE ) THEN
  289. SCALE = ONE / MAX( ABMAX, SAFMIN )
  290. SALFR = SCALE*SALFR
  291. SBETA = SCALE*SBETA
  292. END IF
  293. SCALE = ONE / MAX( ABS( SALFR )*BNORM,
  294. $ ABS( SBETA )*ANORM, SAFMIN )
  295. ACOEF = SCALE*SBETA
  296. BCOEFR = SCALE*SALFR
  297. CALL DGEMV( TRANS, N, N, ACOEF, A, LDA, E( 1, JVEC ), 1,
  298. $ ZERO, WORK( N*( JVEC-1 )+1 ), 1 )
  299. CALL DGEMV( TRANS, N, N, -BCOEFR, B, LDA, E( 1, JVEC ),
  300. $ 1, ONE, WORK( N*( JVEC-1 )+1 ), 1 )
  301. ELSE
  302. *
  303. * Complex conjugate pair
  304. *
  305. ILCPLX = .TRUE.
  306. IF( JVEC.EQ.N ) THEN
  307. RESULT( 1 ) = TEN / ULP
  308. RETURN
  309. END IF
  310. ABMAX = MAX( ABS( SALFR )+ABS( SALFI ), ABS( SBETA ) )
  311. IF( ABS( SALFR )+ABS( SALFI ).GT.ALFMAX .OR.
  312. $ ABS( SBETA ).GT.BETMAX .OR. ABMAX.LT.ONE ) THEN
  313. SCALE = ONE / MAX( ABMAX, SAFMIN )
  314. SALFR = SCALE*SALFR
  315. SALFI = SCALE*SALFI
  316. SBETA = SCALE*SBETA
  317. END IF
  318. SCALE = ONE / MAX( ( ABS( SALFR )+ABS( SALFI ) )*BNORM,
  319. $ ABS( SBETA )*ANORM, SAFMIN )
  320. ACOEF = SCALE*SBETA
  321. BCOEFR = SCALE*SALFR
  322. BCOEFI = SCALE*SALFI
  323. IF( LEFT ) THEN
  324. BCOEFI = -BCOEFI
  325. END IF
  326. *
  327. CALL DGEMV( TRANS, N, N, ACOEF, A, LDA, E( 1, JVEC ), 1,
  328. $ ZERO, WORK( N*( JVEC-1 )+1 ), 1 )
  329. CALL DGEMV( TRANS, N, N, -BCOEFR, B, LDA, E( 1, JVEC ),
  330. $ 1, ONE, WORK( N*( JVEC-1 )+1 ), 1 )
  331. CALL DGEMV( TRANS, N, N, BCOEFI, B, LDA, E( 1, JVEC+1 ),
  332. $ 1, ONE, WORK( N*( JVEC-1 )+1 ), 1 )
  333. *
  334. CALL DGEMV( TRANS, N, N, ACOEF, A, LDA, E( 1, JVEC+1 ),
  335. $ 1, ZERO, WORK( N*JVEC+1 ), 1 )
  336. CALL DGEMV( TRANS, N, N, -BCOEFI, B, LDA, E( 1, JVEC ),
  337. $ 1, ONE, WORK( N*JVEC+1 ), 1 )
  338. CALL DGEMV( TRANS, N, N, -BCOEFR, B, LDA, E( 1, JVEC+1 ),
  339. $ 1, ONE, WORK( N*JVEC+1 ), 1 )
  340. END IF
  341. END IF
  342. 10 CONTINUE
  343. *
  344. ERRNRM = DLANGE( 'One', N, N, WORK, N, WORK( N**2+1 ) ) / ENORM
  345. *
  346. * Compute RESULT(1)
  347. *
  348. RESULT( 1 ) = ERRNRM / ULP
  349. *
  350. * Normalization of E:
  351. *
  352. ENRMER = ZERO
  353. ILCPLX = .FALSE.
  354. DO 40 JVEC = 1, N
  355. IF( ILCPLX ) THEN
  356. ILCPLX = .FALSE.
  357. ELSE
  358. TEMP1 = ZERO
  359. IF( ALPHAI( JVEC ).EQ.ZERO ) THEN
  360. DO 20 J = 1, N
  361. TEMP1 = MAX( TEMP1, ABS( E( J, JVEC ) ) )
  362. 20 CONTINUE
  363. ENRMER = MAX( ENRMER, TEMP1-ONE )
  364. ELSE
  365. ILCPLX = .TRUE.
  366. DO 30 J = 1, N
  367. TEMP1 = MAX( TEMP1, ABS( E( J, JVEC ) )+
  368. $ ABS( E( J, JVEC+1 ) ) )
  369. 30 CONTINUE
  370. ENRMER = MAX( ENRMER, TEMP1-ONE )
  371. END IF
  372. END IF
  373. 40 CONTINUE
  374. *
  375. * Compute RESULT(2) : the normalization error in E.
  376. *
  377. RESULT( 2 ) = ENRMER / ( DBLE( N )*ULP )
  378. *
  379. RETURN
  380. *
  381. * End of DGET52
  382. *
  383. END