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.

ztgevc.f 23 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733
  1. *> \brief \b ZTGEVC
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download ZTGEVC + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/ztgevc.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/ztgevc.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/ztgevc.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE ZTGEVC( SIDE, HOWMNY, SELECT, N, S, LDS, P, LDP, VL,
  22. * LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO )
  23. *
  24. * .. Scalar Arguments ..
  25. * CHARACTER HOWMNY, SIDE
  26. * INTEGER INFO, LDP, LDS, LDVL, LDVR, M, MM, N
  27. * ..
  28. * .. Array Arguments ..
  29. * LOGICAL SELECT( * )
  30. * DOUBLE PRECISION RWORK( * )
  31. * COMPLEX*16 P( LDP, * ), S( LDS, * ), VL( LDVL, * ),
  32. * $ VR( LDVR, * ), WORK( * )
  33. * ..
  34. *
  35. *
  36. *
  37. *> \par Purpose:
  38. * =============
  39. *>
  40. *> \verbatim
  41. *>
  42. *> ZTGEVC computes some or all of the right and/or left eigenvectors of
  43. *> a pair of complex matrices (S,P), where S and P are upper triangular.
  44. *> Matrix pairs of this type are produced by the generalized Schur
  45. *> factorization of a complex matrix pair (A,B):
  46. *>
  47. *> A = Q*S*Z**H, B = Q*P*Z**H
  48. *>
  49. *> as computed by ZGGHRD + ZHGEQZ.
  50. *>
  51. *> The right eigenvector x and the left eigenvector y of (S,P)
  52. *> corresponding to an eigenvalue w are defined by:
  53. *>
  54. *> S*x = w*P*x, (y**H)*S = w*(y**H)*P,
  55. *>
  56. *> where y**H denotes the conjugate transpose of y.
  57. *> The eigenvalues are not input to this routine, but are computed
  58. *> directly from the diagonal elements of S and P.
  59. *>
  60. *> This routine returns the matrices X and/or Y of right and left
  61. *> eigenvectors of (S,P), or the products Z*X and/or Q*Y,
  62. *> where Z and Q are input matrices.
  63. *> If Q and Z are the unitary factors from the generalized Schur
  64. *> factorization of a matrix pair (A,B), then Z*X and Q*Y
  65. *> are the matrices of right and left eigenvectors of (A,B).
  66. *> \endverbatim
  67. *
  68. * Arguments:
  69. * ==========
  70. *
  71. *> \param[in] SIDE
  72. *> \verbatim
  73. *> SIDE is CHARACTER*1
  74. *> = 'R': compute right eigenvectors only;
  75. *> = 'L': compute left eigenvectors only;
  76. *> = 'B': compute both right and left eigenvectors.
  77. *> \endverbatim
  78. *>
  79. *> \param[in] HOWMNY
  80. *> \verbatim
  81. *> HOWMNY is CHARACTER*1
  82. *> = 'A': compute all right and/or left eigenvectors;
  83. *> = 'B': compute all right and/or left eigenvectors,
  84. *> backtransformed by the matrices in VR and/or VL;
  85. *> = 'S': compute selected right and/or left eigenvectors,
  86. *> specified by the logical array SELECT.
  87. *> \endverbatim
  88. *>
  89. *> \param[in] SELECT
  90. *> \verbatim
  91. *> SELECT is LOGICAL array, dimension (N)
  92. *> If HOWMNY='S', SELECT specifies the eigenvectors to be
  93. *> computed. The eigenvector corresponding to the j-th
  94. *> eigenvalue is computed if SELECT(j) = .TRUE..
  95. *> Not referenced if HOWMNY = 'A' or 'B'.
  96. *> \endverbatim
  97. *>
  98. *> \param[in] N
  99. *> \verbatim
  100. *> N is INTEGER
  101. *> The order of the matrices S and P. N >= 0.
  102. *> \endverbatim
  103. *>
  104. *> \param[in] S
  105. *> \verbatim
  106. *> S is COMPLEX*16 array, dimension (LDS,N)
  107. *> The upper triangular matrix S from a generalized Schur
  108. *> factorization, as computed by ZHGEQZ.
  109. *> \endverbatim
  110. *>
  111. *> \param[in] LDS
  112. *> \verbatim
  113. *> LDS is INTEGER
  114. *> The leading dimension of array S. LDS >= max(1,N).
  115. *> \endverbatim
  116. *>
  117. *> \param[in] P
  118. *> \verbatim
  119. *> P is COMPLEX*16 array, dimension (LDP,N)
  120. *> The upper triangular matrix P from a generalized Schur
  121. *> factorization, as computed by ZHGEQZ. P must have real
  122. *> diagonal elements.
  123. *> \endverbatim
  124. *>
  125. *> \param[in] LDP
  126. *> \verbatim
  127. *> LDP is INTEGER
  128. *> The leading dimension of array P. LDP >= max(1,N).
  129. *> \endverbatim
  130. *>
  131. *> \param[in,out] VL
  132. *> \verbatim
  133. *> VL is COMPLEX*16 array, dimension (LDVL,MM)
  134. *> On entry, if SIDE = 'L' or 'B' and HOWMNY = 'B', VL must
  135. *> contain an N-by-N matrix Q (usually the unitary matrix Q
  136. *> of left Schur vectors returned by ZHGEQZ).
  137. *> On exit, if SIDE = 'L' or 'B', VL contains:
  138. *> if HOWMNY = 'A', the matrix Y of left eigenvectors of (S,P);
  139. *> if HOWMNY = 'B', the matrix Q*Y;
  140. *> if HOWMNY = 'S', the left eigenvectors of (S,P) specified by
  141. *> SELECT, stored consecutively in the columns of
  142. *> VL, in the same order as their eigenvalues.
  143. *> Not referenced if SIDE = 'R'.
  144. *> \endverbatim
  145. *>
  146. *> \param[in] LDVL
  147. *> \verbatim
  148. *> LDVL is INTEGER
  149. *> The leading dimension of array VL. LDVL >= 1, and if
  150. *> SIDE = 'L' or 'l' or 'B' or 'b', LDVL >= N.
  151. *> \endverbatim
  152. *>
  153. *> \param[in,out] VR
  154. *> \verbatim
  155. *> VR is COMPLEX*16 array, dimension (LDVR,MM)
  156. *> On entry, if SIDE = 'R' or 'B' and HOWMNY = 'B', VR must
  157. *> contain an N-by-N matrix Z (usually the unitary matrix Z
  158. *> of right Schur vectors returned by ZHGEQZ).
  159. *> On exit, if SIDE = 'R' or 'B', VR contains:
  160. *> if HOWMNY = 'A', the matrix X of right eigenvectors of (S,P);
  161. *> if HOWMNY = 'B', the matrix Z*X;
  162. *> if HOWMNY = 'S', the right eigenvectors of (S,P) specified by
  163. *> SELECT, stored consecutively in the columns of
  164. *> VR, in the same order as their eigenvalues.
  165. *> Not referenced if SIDE = 'L'.
  166. *> \endverbatim
  167. *>
  168. *> \param[in] LDVR
  169. *> \verbatim
  170. *> LDVR is INTEGER
  171. *> The leading dimension of the array VR. LDVR >= 1, and if
  172. *> SIDE = 'R' or 'B', LDVR >= N.
  173. *> \endverbatim
  174. *>
  175. *> \param[in] MM
  176. *> \verbatim
  177. *> MM is INTEGER
  178. *> The number of columns in the arrays VL and/or VR. MM >= M.
  179. *> \endverbatim
  180. *>
  181. *> \param[out] M
  182. *> \verbatim
  183. *> M is INTEGER
  184. *> The number of columns in the arrays VL and/or VR actually
  185. *> used to store the eigenvectors. If HOWMNY = 'A' or 'B', M
  186. *> is set to N. Each selected eigenvector occupies one column.
  187. *> \endverbatim
  188. *>
  189. *> \param[out] WORK
  190. *> \verbatim
  191. *> WORK is COMPLEX*16 array, dimension (2*N)
  192. *> \endverbatim
  193. *>
  194. *> \param[out] RWORK
  195. *> \verbatim
  196. *> RWORK is DOUBLE PRECISION array, dimension (2*N)
  197. *> \endverbatim
  198. *>
  199. *> \param[out] INFO
  200. *> \verbatim
  201. *> INFO is INTEGER
  202. *> = 0: successful exit.
  203. *> < 0: if INFO = -i, the i-th argument had an illegal value.
  204. *> \endverbatim
  205. *
  206. * Authors:
  207. * ========
  208. *
  209. *> \author Univ. of Tennessee
  210. *> \author Univ. of California Berkeley
  211. *> \author Univ. of Colorado Denver
  212. *> \author NAG Ltd.
  213. *
  214. *> \ingroup complex16GEcomputational
  215. *
  216. * =====================================================================
  217. SUBROUTINE ZTGEVC( SIDE, HOWMNY, SELECT, N, S, LDS, P, LDP, VL,
  218. $ LDVL, VR, LDVR, MM, M, WORK, RWORK, INFO )
  219. *
  220. * -- LAPACK computational routine --
  221. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  222. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  223. *
  224. * .. Scalar Arguments ..
  225. CHARACTER HOWMNY, SIDE
  226. INTEGER INFO, LDP, LDS, LDVL, LDVR, M, MM, N
  227. * ..
  228. * .. Array Arguments ..
  229. LOGICAL SELECT( * )
  230. DOUBLE PRECISION RWORK( * )
  231. COMPLEX*16 P( LDP, * ), S( LDS, * ), VL( LDVL, * ),
  232. $ VR( LDVR, * ), WORK( * )
  233. * ..
  234. *
  235. *
  236. * =====================================================================
  237. *
  238. * .. Parameters ..
  239. DOUBLE PRECISION ZERO, ONE
  240. PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
  241. COMPLEX*16 CZERO, CONE
  242. PARAMETER ( CZERO = ( 0.0D+0, 0.0D+0 ),
  243. $ CONE = ( 1.0D+0, 0.0D+0 ) )
  244. * ..
  245. * .. Local Scalars ..
  246. LOGICAL COMPL, COMPR, ILALL, ILBACK, ILBBAD, ILCOMP,
  247. $ LSA, LSB
  248. INTEGER I, IBEG, IEIG, IEND, IHWMNY, IM, ISIDE, ISRC,
  249. $ J, JE, JR
  250. DOUBLE PRECISION ACOEFA, ACOEFF, ANORM, ASCALE, BCOEFA, BIG,
  251. $ BIGNUM, BNORM, BSCALE, DMIN, SAFMIN, SBETA,
  252. $ SCALE, SMALL, TEMP, ULP, XMAX
  253. COMPLEX*16 BCOEFF, CA, CB, D, SALPHA, SUM, SUMA, SUMB, X
  254. * ..
  255. * .. External Functions ..
  256. LOGICAL LSAME
  257. DOUBLE PRECISION DLAMCH
  258. COMPLEX*16 ZLADIV
  259. EXTERNAL LSAME, DLAMCH, ZLADIV
  260. * ..
  261. * .. External Subroutines ..
  262. EXTERNAL XERBLA, ZGEMV
  263. * ..
  264. * .. Intrinsic Functions ..
  265. INTRINSIC ABS, DBLE, DCMPLX, DCONJG, DIMAG, MAX, MIN
  266. * ..
  267. * .. Statement Functions ..
  268. DOUBLE PRECISION ABS1
  269. * ..
  270. * .. Statement Function definitions ..
  271. ABS1( X ) = ABS( DBLE( X ) ) + ABS( DIMAG( X ) )
  272. * ..
  273. * .. Executable Statements ..
  274. *
  275. * Decode and Test the input parameters
  276. *
  277. IF( LSAME( HOWMNY, 'A' ) ) THEN
  278. IHWMNY = 1
  279. ILALL = .TRUE.
  280. ILBACK = .FALSE.
  281. ELSE IF( LSAME( HOWMNY, 'S' ) ) THEN
  282. IHWMNY = 2
  283. ILALL = .FALSE.
  284. ILBACK = .FALSE.
  285. ELSE IF( LSAME( HOWMNY, 'B' ) ) THEN
  286. IHWMNY = 3
  287. ILALL = .TRUE.
  288. ILBACK = .TRUE.
  289. ELSE
  290. IHWMNY = -1
  291. END IF
  292. *
  293. IF( LSAME( SIDE, 'R' ) ) THEN
  294. ISIDE = 1
  295. COMPL = .FALSE.
  296. COMPR = .TRUE.
  297. ELSE IF( LSAME( SIDE, 'L' ) ) THEN
  298. ISIDE = 2
  299. COMPL = .TRUE.
  300. COMPR = .FALSE.
  301. ELSE IF( LSAME( SIDE, 'B' ) ) THEN
  302. ISIDE = 3
  303. COMPL = .TRUE.
  304. COMPR = .TRUE.
  305. ELSE
  306. ISIDE = -1
  307. END IF
  308. *
  309. INFO = 0
  310. IF( ISIDE.LT.0 ) THEN
  311. INFO = -1
  312. ELSE IF( IHWMNY.LT.0 ) THEN
  313. INFO = -2
  314. ELSE IF( N.LT.0 ) THEN
  315. INFO = -4
  316. ELSE IF( LDS.LT.MAX( 1, N ) ) THEN
  317. INFO = -6
  318. ELSE IF( LDP.LT.MAX( 1, N ) ) THEN
  319. INFO = -8
  320. END IF
  321. IF( INFO.NE.0 ) THEN
  322. CALL XERBLA( 'ZTGEVC', -INFO )
  323. RETURN
  324. END IF
  325. *
  326. * Count the number of eigenvectors
  327. *
  328. IF( .NOT.ILALL ) THEN
  329. IM = 0
  330. DO 10 J = 1, N
  331. IF( SELECT( J ) )
  332. $ IM = IM + 1
  333. 10 CONTINUE
  334. ELSE
  335. IM = N
  336. END IF
  337. *
  338. * Check diagonal of B
  339. *
  340. ILBBAD = .FALSE.
  341. DO 20 J = 1, N
  342. IF( DIMAG( P( J, J ) ).NE.ZERO )
  343. $ ILBBAD = .TRUE.
  344. 20 CONTINUE
  345. *
  346. IF( ILBBAD ) THEN
  347. INFO = -7
  348. ELSE IF( COMPL .AND. LDVL.LT.N .OR. LDVL.LT.1 ) THEN
  349. INFO = -10
  350. ELSE IF( COMPR .AND. LDVR.LT.N .OR. LDVR.LT.1 ) THEN
  351. INFO = -12
  352. ELSE IF( MM.LT.IM ) THEN
  353. INFO = -13
  354. END IF
  355. IF( INFO.NE.0 ) THEN
  356. CALL XERBLA( 'ZTGEVC', -INFO )
  357. RETURN
  358. END IF
  359. *
  360. * Quick return if possible
  361. *
  362. M = IM
  363. IF( N.EQ.0 )
  364. $ RETURN
  365. *
  366. * Machine Constants
  367. *
  368. SAFMIN = DLAMCH( 'Safe minimum' )
  369. BIG = ONE / SAFMIN
  370. ULP = DLAMCH( 'Epsilon' )*DLAMCH( 'Base' )
  371. SMALL = SAFMIN*N / ULP
  372. BIG = ONE / SMALL
  373. BIGNUM = ONE / ( SAFMIN*N )
  374. *
  375. * Compute the 1-norm of each column of the strictly upper triangular
  376. * part of A and B to check for possible overflow in the triangular
  377. * solver.
  378. *
  379. ANORM = ABS1( S( 1, 1 ) )
  380. BNORM = ABS1( P( 1, 1 ) )
  381. RWORK( 1 ) = ZERO
  382. RWORK( N+1 ) = ZERO
  383. DO 40 J = 2, N
  384. RWORK( J ) = ZERO
  385. RWORK( N+J ) = ZERO
  386. DO 30 I = 1, J - 1
  387. RWORK( J ) = RWORK( J ) + ABS1( S( I, J ) )
  388. RWORK( N+J ) = RWORK( N+J ) + ABS1( P( I, J ) )
  389. 30 CONTINUE
  390. ANORM = MAX( ANORM, RWORK( J )+ABS1( S( J, J ) ) )
  391. BNORM = MAX( BNORM, RWORK( N+J )+ABS1( P( J, J ) ) )
  392. 40 CONTINUE
  393. *
  394. ASCALE = ONE / MAX( ANORM, SAFMIN )
  395. BSCALE = ONE / MAX( BNORM, SAFMIN )
  396. *
  397. * Left eigenvectors
  398. *
  399. IF( COMPL ) THEN
  400. IEIG = 0
  401. *
  402. * Main loop over eigenvalues
  403. *
  404. DO 140 JE = 1, N
  405. IF( ILALL ) THEN
  406. ILCOMP = .TRUE.
  407. ELSE
  408. ILCOMP = SELECT( JE )
  409. END IF
  410. IF( ILCOMP ) THEN
  411. IEIG = IEIG + 1
  412. *
  413. IF( ABS1( S( JE, JE ) ).LE.SAFMIN .AND.
  414. $ ABS( DBLE( P( JE, JE ) ) ).LE.SAFMIN ) THEN
  415. *
  416. * Singular matrix pencil -- return unit eigenvector
  417. *
  418. DO 50 JR = 1, N
  419. VL( JR, IEIG ) = CZERO
  420. 50 CONTINUE
  421. VL( IEIG, IEIG ) = CONE
  422. GO TO 140
  423. END IF
  424. *
  425. * Non-singular eigenvalue:
  426. * Compute coefficients a and b in
  427. * H
  428. * y ( a A - b B ) = 0
  429. *
  430. TEMP = ONE / MAX( ABS1( S( JE, JE ) )*ASCALE,
  431. $ ABS( DBLE( P( JE, JE ) ) )*BSCALE, SAFMIN )
  432. SALPHA = ( TEMP*S( JE, JE ) )*ASCALE
  433. SBETA = ( TEMP*DBLE( P( JE, JE ) ) )*BSCALE
  434. ACOEFF = SBETA*ASCALE
  435. BCOEFF = SALPHA*BSCALE
  436. *
  437. * Scale to avoid underflow
  438. *
  439. LSA = ABS( SBETA ).GE.SAFMIN .AND. ABS( ACOEFF ).LT.SMALL
  440. LSB = ABS1( SALPHA ).GE.SAFMIN .AND. ABS1( BCOEFF ).LT.
  441. $ SMALL
  442. *
  443. SCALE = ONE
  444. IF( LSA )
  445. $ SCALE = ( SMALL / ABS( SBETA ) )*MIN( ANORM, BIG )
  446. IF( LSB )
  447. $ SCALE = MAX( SCALE, ( SMALL / ABS1( SALPHA ) )*
  448. $ MIN( BNORM, BIG ) )
  449. IF( LSA .OR. LSB ) THEN
  450. SCALE = MIN( SCALE, ONE /
  451. $ ( SAFMIN*MAX( ONE, ABS( ACOEFF ),
  452. $ ABS1( BCOEFF ) ) ) )
  453. IF( LSA ) THEN
  454. ACOEFF = ASCALE*( SCALE*SBETA )
  455. ELSE
  456. ACOEFF = SCALE*ACOEFF
  457. END IF
  458. IF( LSB ) THEN
  459. BCOEFF = BSCALE*( SCALE*SALPHA )
  460. ELSE
  461. BCOEFF = SCALE*BCOEFF
  462. END IF
  463. END IF
  464. *
  465. ACOEFA = ABS( ACOEFF )
  466. BCOEFA = ABS1( BCOEFF )
  467. XMAX = ONE
  468. DO 60 JR = 1, N
  469. WORK( JR ) = CZERO
  470. 60 CONTINUE
  471. WORK( JE ) = CONE
  472. DMIN = MAX( ULP*ACOEFA*ANORM, ULP*BCOEFA*BNORM, SAFMIN )
  473. *
  474. * H
  475. * Triangular solve of (a A - b B) y = 0
  476. *
  477. * H
  478. * (rowwise in (a A - b B) , or columnwise in a A - b B)
  479. *
  480. DO 100 J = JE + 1, N
  481. *
  482. * Compute
  483. * j-1
  484. * SUM = sum conjg( a*S(k,j) - b*P(k,j) )*x(k)
  485. * k=je
  486. * (Scale if necessary)
  487. *
  488. TEMP = ONE / XMAX
  489. IF( ACOEFA*RWORK( J )+BCOEFA*RWORK( N+J ).GT.BIGNUM*
  490. $ TEMP ) THEN
  491. DO 70 JR = JE, J - 1
  492. WORK( JR ) = TEMP*WORK( JR )
  493. 70 CONTINUE
  494. XMAX = ONE
  495. END IF
  496. SUMA = CZERO
  497. SUMB = CZERO
  498. *
  499. DO 80 JR = JE, J - 1
  500. SUMA = SUMA + DCONJG( S( JR, J ) )*WORK( JR )
  501. SUMB = SUMB + DCONJG( P( JR, J ) )*WORK( JR )
  502. 80 CONTINUE
  503. SUM = ACOEFF*SUMA - DCONJG( BCOEFF )*SUMB
  504. *
  505. * Form x(j) = - SUM / conjg( a*S(j,j) - b*P(j,j) )
  506. *
  507. * with scaling and perturbation of the denominator
  508. *
  509. D = DCONJG( ACOEFF*S( J, J )-BCOEFF*P( J, J ) )
  510. IF( ABS1( D ).LE.DMIN )
  511. $ D = DCMPLX( DMIN )
  512. *
  513. IF( ABS1( D ).LT.ONE ) THEN
  514. IF( ABS1( SUM ).GE.BIGNUM*ABS1( D ) ) THEN
  515. TEMP = ONE / ABS1( SUM )
  516. DO 90 JR = JE, J - 1
  517. WORK( JR ) = TEMP*WORK( JR )
  518. 90 CONTINUE
  519. XMAX = TEMP*XMAX
  520. SUM = TEMP*SUM
  521. END IF
  522. END IF
  523. WORK( J ) = ZLADIV( -SUM, D )
  524. XMAX = MAX( XMAX, ABS1( WORK( J ) ) )
  525. 100 CONTINUE
  526. *
  527. * Back transform eigenvector if HOWMNY='B'.
  528. *
  529. IF( ILBACK ) THEN
  530. CALL ZGEMV( 'N', N, N+1-JE, CONE, VL( 1, JE ), LDVL,
  531. $ WORK( JE ), 1, CZERO, WORK( N+1 ), 1 )
  532. ISRC = 2
  533. IBEG = 1
  534. ELSE
  535. ISRC = 1
  536. IBEG = JE
  537. END IF
  538. *
  539. * Copy and scale eigenvector into column of VL
  540. *
  541. XMAX = ZERO
  542. DO 110 JR = IBEG, N
  543. XMAX = MAX( XMAX, ABS1( WORK( ( ISRC-1 )*N+JR ) ) )
  544. 110 CONTINUE
  545. *
  546. IF( XMAX.GT.SAFMIN ) THEN
  547. TEMP = ONE / XMAX
  548. DO 120 JR = IBEG, N
  549. VL( JR, IEIG ) = TEMP*WORK( ( ISRC-1 )*N+JR )
  550. 120 CONTINUE
  551. ELSE
  552. IBEG = N + 1
  553. END IF
  554. *
  555. DO 130 JR = 1, IBEG - 1
  556. VL( JR, IEIG ) = CZERO
  557. 130 CONTINUE
  558. *
  559. END IF
  560. 140 CONTINUE
  561. END IF
  562. *
  563. * Right eigenvectors
  564. *
  565. IF( COMPR ) THEN
  566. IEIG = IM + 1
  567. *
  568. * Main loop over eigenvalues
  569. *
  570. DO 250 JE = N, 1, -1
  571. IF( ILALL ) THEN
  572. ILCOMP = .TRUE.
  573. ELSE
  574. ILCOMP = SELECT( JE )
  575. END IF
  576. IF( ILCOMP ) THEN
  577. IEIG = IEIG - 1
  578. *
  579. IF( ABS1( S( JE, JE ) ).LE.SAFMIN .AND.
  580. $ ABS( DBLE( P( JE, JE ) ) ).LE.SAFMIN ) THEN
  581. *
  582. * Singular matrix pencil -- return unit eigenvector
  583. *
  584. DO 150 JR = 1, N
  585. VR( JR, IEIG ) = CZERO
  586. 150 CONTINUE
  587. VR( IEIG, IEIG ) = CONE
  588. GO TO 250
  589. END IF
  590. *
  591. * Non-singular eigenvalue:
  592. * Compute coefficients a and b in
  593. *
  594. * ( a A - b B ) x = 0
  595. *
  596. TEMP = ONE / MAX( ABS1( S( JE, JE ) )*ASCALE,
  597. $ ABS( DBLE( P( JE, JE ) ) )*BSCALE, SAFMIN )
  598. SALPHA = ( TEMP*S( JE, JE ) )*ASCALE
  599. SBETA = ( TEMP*DBLE( P( JE, JE ) ) )*BSCALE
  600. ACOEFF = SBETA*ASCALE
  601. BCOEFF = SALPHA*BSCALE
  602. *
  603. * Scale to avoid underflow
  604. *
  605. LSA = ABS( SBETA ).GE.SAFMIN .AND. ABS( ACOEFF ).LT.SMALL
  606. LSB = ABS1( SALPHA ).GE.SAFMIN .AND. ABS1( BCOEFF ).LT.
  607. $ SMALL
  608. *
  609. SCALE = ONE
  610. IF( LSA )
  611. $ SCALE = ( SMALL / ABS( SBETA ) )*MIN( ANORM, BIG )
  612. IF( LSB )
  613. $ SCALE = MAX( SCALE, ( SMALL / ABS1( SALPHA ) )*
  614. $ MIN( BNORM, BIG ) )
  615. IF( LSA .OR. LSB ) THEN
  616. SCALE = MIN( SCALE, ONE /
  617. $ ( SAFMIN*MAX( ONE, ABS( ACOEFF ),
  618. $ ABS1( BCOEFF ) ) ) )
  619. IF( LSA ) THEN
  620. ACOEFF = ASCALE*( SCALE*SBETA )
  621. ELSE
  622. ACOEFF = SCALE*ACOEFF
  623. END IF
  624. IF( LSB ) THEN
  625. BCOEFF = BSCALE*( SCALE*SALPHA )
  626. ELSE
  627. BCOEFF = SCALE*BCOEFF
  628. END IF
  629. END IF
  630. *
  631. ACOEFA = ABS( ACOEFF )
  632. BCOEFA = ABS1( BCOEFF )
  633. XMAX = ONE
  634. DO 160 JR = 1, N
  635. WORK( JR ) = CZERO
  636. 160 CONTINUE
  637. WORK( JE ) = CONE
  638. DMIN = MAX( ULP*ACOEFA*ANORM, ULP*BCOEFA*BNORM, SAFMIN )
  639. *
  640. * Triangular solve of (a A - b B) x = 0 (columnwise)
  641. *
  642. * WORK(1:j-1) contains sums w,
  643. * WORK(j+1:JE) contains x
  644. *
  645. DO 170 JR = 1, JE - 1
  646. WORK( JR ) = ACOEFF*S( JR, JE ) - BCOEFF*P( JR, JE )
  647. 170 CONTINUE
  648. WORK( JE ) = CONE
  649. *
  650. DO 210 J = JE - 1, 1, -1
  651. *
  652. * Form x(j) := - w(j) / d
  653. * with scaling and perturbation of the denominator
  654. *
  655. D = ACOEFF*S( J, J ) - BCOEFF*P( J, J )
  656. IF( ABS1( D ).LE.DMIN )
  657. $ D = DCMPLX( DMIN )
  658. *
  659. IF( ABS1( D ).LT.ONE ) THEN
  660. IF( ABS1( WORK( J ) ).GE.BIGNUM*ABS1( D ) ) THEN
  661. TEMP = ONE / ABS1( WORK( J ) )
  662. DO 180 JR = 1, JE
  663. WORK( JR ) = TEMP*WORK( JR )
  664. 180 CONTINUE
  665. END IF
  666. END IF
  667. *
  668. WORK( J ) = ZLADIV( -WORK( J ), D )
  669. *
  670. IF( J.GT.1 ) THEN
  671. *
  672. * w = w + x(j)*(a S(*,j) - b P(*,j) ) with scaling
  673. *
  674. IF( ABS1( WORK( J ) ).GT.ONE ) THEN
  675. TEMP = ONE / ABS1( WORK( J ) )
  676. IF( ACOEFA*RWORK( J )+BCOEFA*RWORK( N+J ).GE.
  677. $ BIGNUM*TEMP ) THEN
  678. DO 190 JR = 1, JE
  679. WORK( JR ) = TEMP*WORK( JR )
  680. 190 CONTINUE
  681. END IF
  682. END IF
  683. *
  684. CA = ACOEFF*WORK( J )
  685. CB = BCOEFF*WORK( J )
  686. DO 200 JR = 1, J - 1
  687. WORK( JR ) = WORK( JR ) + CA*S( JR, J ) -
  688. $ CB*P( JR, J )
  689. 200 CONTINUE
  690. END IF
  691. 210 CONTINUE
  692. *
  693. * Back transform eigenvector if HOWMNY='B'.
  694. *
  695. IF( ILBACK ) THEN
  696. CALL ZGEMV( 'N', N, JE, CONE, VR, LDVR, WORK, 1,
  697. $ CZERO, WORK( N+1 ), 1 )
  698. ISRC = 2
  699. IEND = N
  700. ELSE
  701. ISRC = 1
  702. IEND = JE
  703. END IF
  704. *
  705. * Copy and scale eigenvector into column of VR
  706. *
  707. XMAX = ZERO
  708. DO 220 JR = 1, IEND
  709. XMAX = MAX( XMAX, ABS1( WORK( ( ISRC-1 )*N+JR ) ) )
  710. 220 CONTINUE
  711. *
  712. IF( XMAX.GT.SAFMIN ) THEN
  713. TEMP = ONE / XMAX
  714. DO 230 JR = 1, IEND
  715. VR( JR, IEIG ) = TEMP*WORK( ( ISRC-1 )*N+JR )
  716. 230 CONTINUE
  717. ELSE
  718. IEND = 0
  719. END IF
  720. *
  721. DO 240 JR = IEND + 1, N
  722. VR( JR, IEIG ) = CZERO
  723. 240 CONTINUE
  724. *
  725. END IF
  726. 250 CONTINUE
  727. END IF
  728. *
  729. RETURN
  730. *
  731. * End of ZTGEVC
  732. *
  733. END