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.

cgebal.f 12 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418
  1. *> \brief \b CGEBAL
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download CGEBAL + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/cgebal.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/cgebal.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/cgebal.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE CGEBAL( JOB, N, A, LDA, ILO, IHI, SCALE, INFO )
  22. *
  23. * .. Scalar Arguments ..
  24. * CHARACTER JOB
  25. * INTEGER IHI, ILO, INFO, LDA, N
  26. * ..
  27. * .. Array Arguments ..
  28. * REAL SCALE( * )
  29. * COMPLEX A( LDA, * )
  30. * ..
  31. *
  32. *
  33. *> \par Purpose:
  34. * =============
  35. *>
  36. *> \verbatim
  37. *>
  38. *> CGEBAL balances a general complex matrix A. This involves, first,
  39. *> permuting A by a similarity transformation to isolate eigenvalues
  40. *> in the first 1 to ILO-1 and last IHI+1 to N elements on the
  41. *> diagonal; and second, applying a diagonal similarity transformation
  42. *> to rows and columns ILO to IHI to make the rows and columns as
  43. *> close in norm as possible. Both steps are optional.
  44. *>
  45. *> Balancing may reduce the 1-norm of the matrix, and improve the
  46. *> accuracy of the computed eigenvalues and/or eigenvectors.
  47. *> \endverbatim
  48. *
  49. * Arguments:
  50. * ==========
  51. *
  52. *> \param[in] JOB
  53. *> \verbatim
  54. *> JOB is CHARACTER*1
  55. *> Specifies the operations to be performed on A:
  56. *> = 'N': none: simply set ILO = 1, IHI = N, SCALE(I) = 1.0
  57. *> for i = 1,...,N;
  58. *> = 'P': permute only;
  59. *> = 'S': scale only;
  60. *> = 'B': both permute and scale.
  61. *> \endverbatim
  62. *>
  63. *> \param[in] N
  64. *> \verbatim
  65. *> N is INTEGER
  66. *> The order of the matrix A. N >= 0.
  67. *> \endverbatim
  68. *>
  69. *> \param[in,out] A
  70. *> \verbatim
  71. *> A is COMPLEX array, dimension (LDA,N)
  72. *> On entry, the input matrix A.
  73. *> On exit, A is overwritten by the balanced matrix.
  74. *> If JOB = 'N', A is not referenced.
  75. *> See Further Details.
  76. *> \endverbatim
  77. *>
  78. *> \param[in] LDA
  79. *> \verbatim
  80. *> LDA is INTEGER
  81. *> The leading dimension of the array A. LDA >= max(1,N).
  82. *> \endverbatim
  83. *>
  84. *> \param[out] ILO
  85. *> \verbatim
  86. *> ILO is INTEGER
  87. *> \endverbatim
  88. *>
  89. *> \param[out] IHI
  90. *> \verbatim
  91. *> IHI is INTEGER
  92. *> ILO and IHI are set to integers such that on exit
  93. *> A(i,j) = 0 if i > j and j = 1,...,ILO-1 or I = IHI+1,...,N.
  94. *> If JOB = 'N' or 'S', ILO = 1 and IHI = N.
  95. *> \endverbatim
  96. *>
  97. *> \param[out] SCALE
  98. *> \verbatim
  99. *> SCALE is REAL array, dimension (N)
  100. *> Details of the permutations and scaling factors applied to
  101. *> A. If P(j) is the index of the row and column interchanged
  102. *> with row and column j and D(j) is the scaling factor
  103. *> applied to row and column j, then
  104. *> SCALE(j) = P(j) for j = 1,...,ILO-1
  105. *> = D(j) for j = ILO,...,IHI
  106. *> = P(j) for j = IHI+1,...,N.
  107. *> The order in which the interchanges are made is N to IHI+1,
  108. *> then 1 to ILO-1.
  109. *> \endverbatim
  110. *>
  111. *> \param[out] INFO
  112. *> \verbatim
  113. *> INFO is INTEGER
  114. *> = 0: successful exit.
  115. *> < 0: if INFO = -i, the i-th argument had an illegal value.
  116. *> \endverbatim
  117. *
  118. * Authors:
  119. * ========
  120. *
  121. *> \author Univ. of Tennessee
  122. *> \author Univ. of California Berkeley
  123. *> \author Univ. of Colorado Denver
  124. *> \author NAG Ltd.
  125. *
  126. *> \ingroup complexGEcomputational
  127. *
  128. *> \par Further Details:
  129. * =====================
  130. *>
  131. *> \verbatim
  132. *>
  133. *> The permutations consist of row and column interchanges which put
  134. *> the matrix in the form
  135. *>
  136. *> ( T1 X Y )
  137. *> P A P = ( 0 B Z )
  138. *> ( 0 0 T2 )
  139. *>
  140. *> where T1 and T2 are upper triangular matrices whose eigenvalues lie
  141. *> along the diagonal. The column indices ILO and IHI mark the starting
  142. *> and ending columns of the submatrix B. Balancing consists of applying
  143. *> a diagonal similarity transformation inv(D) * B * D to make the
  144. *> 1-norms of each row of B and its corresponding column nearly equal.
  145. *> The output matrix is
  146. *>
  147. *> ( T1 X*D Y )
  148. *> ( 0 inv(D)*B*D inv(D)*Z ).
  149. *> ( 0 0 T2 )
  150. *>
  151. *> Information about the permutations P and the diagonal matrix D is
  152. *> returned in the vector SCALE.
  153. *>
  154. *> This subroutine is based on the EISPACK routine CBAL.
  155. *>
  156. *> Modified by Tzu-Yi Chen, Computer Science Division, University of
  157. *> California at Berkeley, USA
  158. *>
  159. *> Refactored by Evert Provoost, Department of Computer Science,
  160. *> KU Leuven, Belgium
  161. *> \endverbatim
  162. *>
  163. * =====================================================================
  164. SUBROUTINE CGEBAL( JOB, N, A, LDA, ILO, IHI, SCALE, INFO )
  165. *
  166. * -- LAPACK computational routine --
  167. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  168. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  169. *
  170. * .. Scalar Arguments ..
  171. CHARACTER JOB
  172. INTEGER IHI, ILO, INFO, LDA, N
  173. * ..
  174. * .. Array Arguments ..
  175. REAL SCALE( * )
  176. COMPLEX A( LDA, * )
  177. * ..
  178. *
  179. * =====================================================================
  180. *
  181. * .. Parameters ..
  182. REAL ZERO, ONE
  183. PARAMETER ( ZERO = 0.0E+0, ONE = 1.0E+0 )
  184. REAL SCLFAC
  185. PARAMETER ( SCLFAC = 2.0E+0 )
  186. REAL FACTOR
  187. PARAMETER ( FACTOR = 0.95E+0 )
  188. * ..
  189. * .. Local Scalars ..
  190. LOGICAL NOCONV, CANSWAP
  191. INTEGER I, ICA, IRA, J, K, L
  192. REAL C, CA, F, G, R, RA, S, SFMAX1, SFMAX2, SFMIN1,
  193. $ SFMIN2
  194. * ..
  195. * .. External Functions ..
  196. LOGICAL SISNAN, LSAME
  197. INTEGER ICAMAX
  198. REAL SLAMCH, SCNRM2
  199. EXTERNAL SISNAN, LSAME, ICAMAX, SLAMCH, SCNRM2
  200. * ..
  201. * .. External Subroutines ..
  202. EXTERNAL XERBLA, CSSCAL, CSWAP
  203. * ..
  204. * .. Intrinsic Functions ..
  205. INTRINSIC ABS, REAL, AIMAG, MAX, MIN
  206. *
  207. * Test the input parameters
  208. *
  209. INFO = 0
  210. IF( .NOT.LSAME( JOB, 'N' ) .AND. .NOT.LSAME( JOB, 'P' ) .AND.
  211. $ .NOT.LSAME( JOB, 'S' ) .AND. .NOT.LSAME( JOB, 'B' ) ) THEN
  212. INFO = -1
  213. ELSE IF( N.LT.0 ) THEN
  214. INFO = -2
  215. ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
  216. INFO = -4
  217. END IF
  218. IF( INFO.NE.0 ) THEN
  219. CALL XERBLA( 'CGEBAL', -INFO )
  220. RETURN
  221. END IF
  222. *
  223. * Quick returns.
  224. *
  225. IF( N.EQ.0 ) THEN
  226. ILO = 1
  227. IHI = 0
  228. RETURN
  229. END IF
  230. *
  231. IF( LSAME( JOB, 'N' ) ) THEN
  232. DO I = 1, N
  233. SCALE( I ) = ONE
  234. END DO
  235. ILO = 1
  236. IHI = N
  237. RETURN
  238. END IF
  239. *
  240. * Permutation to isolate eigenvalues if possible.
  241. *
  242. K = 1
  243. L = N
  244. *
  245. IF( .NOT.LSAME( JOB, 'S' ) ) THEN
  246. *
  247. * Row and column exchange.
  248. *
  249. NOCONV = .TRUE.
  250. DO WHILE( NOCONV )
  251. *
  252. * Search for rows isolating an eigenvalue and push them down.
  253. *
  254. NOCONV = .FALSE.
  255. DO I = L, 1, -1
  256. CANSWAP = .TRUE.
  257. DO J = 1, L
  258. IF( I.NE.J .AND. ( REAL( A( I, J ) ).NE.ZERO .OR.
  259. $ AIMAG( A( I, J ) ).NE.ZERO ) ) THEN
  260. CANSWAP = .FALSE.
  261. EXIT
  262. END IF
  263. END DO
  264. *
  265. IF( CANSWAP ) THEN
  266. SCALE( L ) = I
  267. IF( I.NE.L ) THEN
  268. CALL CSWAP( L, A( 1, I ), 1, A( 1, L ), 1 )
  269. CALL CSWAP( N-K+1, A( I, K ), LDA, A( L, K ), LDA )
  270. END IF
  271. NOCONV = .TRUE.
  272. *
  273. IF( L.EQ.1 ) THEN
  274. ILO = 1
  275. IHI = 1
  276. RETURN
  277. END IF
  278. *
  279. L = L - 1
  280. END IF
  281. END DO
  282. *
  283. END DO
  284. NOCONV = .TRUE.
  285. DO WHILE( NOCONV )
  286. *
  287. * Search for columns isolating an eigenvalue and push them left.
  288. *
  289. NOCONV = .FALSE.
  290. DO J = K, L
  291. CANSWAP = .TRUE.
  292. DO I = K, L
  293. IF( I.NE.J .AND. ( REAL( A( I, J ) ).NE.ZERO .OR.
  294. $ AIMAG( A( I, J ) ).NE.ZERO ) ) THEN
  295. CANSWAP = .FALSE.
  296. EXIT
  297. END IF
  298. END DO
  299. *
  300. IF( CANSWAP ) THEN
  301. SCALE( K ) = J
  302. IF( J.NE.K ) THEN
  303. CALL CSWAP( L, A( 1, J ), 1, A( 1, K ), 1 )
  304. CALL CSWAP( N-K+1, A( J, K ), LDA, A( K, K ), LDA )
  305. END IF
  306. NOCONV = .TRUE.
  307. *
  308. K = K + 1
  309. END IF
  310. END DO
  311. *
  312. END DO
  313. *
  314. END IF
  315. *
  316. * Initialize SCALE for non-permuted submatrix.
  317. *
  318. DO I = K, L
  319. SCALE( I ) = ONE
  320. END DO
  321. *
  322. * If we only had to permute, we are done.
  323. *
  324. IF( LSAME( JOB, 'P' ) ) THEN
  325. ILO = K
  326. IHI = L
  327. RETURN
  328. END IF
  329. *
  330. * Balance the submatrix in rows K to L.
  331. *
  332. * Iterative loop for norm reduction.
  333. *
  334. SFMIN1 = SLAMCH( 'S' ) / SLAMCH( 'P' )
  335. SFMAX1 = ONE / SFMIN1
  336. SFMIN2 = SFMIN1*SCLFAC
  337. SFMAX2 = ONE / SFMIN2
  338. *
  339. NOCONV = .TRUE.
  340. DO WHILE( NOCONV )
  341. NOCONV = .FALSE.
  342. *
  343. DO I = K, L
  344. *
  345. C = SCNRM2( L-K+1, A( K, I ), 1 )
  346. R = SCNRM2( L-K+1, A( I, K ), LDA )
  347. ICA = ICAMAX( L, A( 1, I ), 1 )
  348. CA = ABS( A( ICA, I ) )
  349. IRA = ICAMAX( N-K+1, A( I, K ), LDA )
  350. RA = ABS( A( I, IRA+K-1 ) )
  351. *
  352. * Guard against zero C or R due to underflow.
  353. *
  354. IF( C.EQ.ZERO .OR. R.EQ.ZERO ) CYCLE
  355. *
  356. * Exit if NaN to avoid infinite loop
  357. *
  358. IF( SISNAN( C+CA+R+RA ) ) THEN
  359. INFO = -3
  360. CALL XERBLA( 'CGEBAL', -INFO )
  361. RETURN
  362. END IF
  363. *
  364. G = R / SCLFAC
  365. F = ONE
  366. S = C + R
  367. *
  368. DO WHILE( C.LT.G .AND. MAX( F, C, CA ).LT.SFMAX2 .AND.
  369. $ MIN( R, G, RA ).GT.SFMIN2 )
  370. F = F*SCLFAC
  371. C = C*SCLFAC
  372. CA = CA*SCLFAC
  373. R = R / SCLFAC
  374. G = G / SCLFAC
  375. RA = RA / SCLFAC
  376. END DO
  377. *
  378. G = C / SCLFAC
  379. *
  380. DO WHILE( G.GE.R .AND. MAX( R, RA ).LT.SFMAX2 .AND.
  381. $ MIN( F, C, G, CA ).GT.SFMIN2 )
  382. F = F / SCLFAC
  383. C = C / SCLFAC
  384. G = G / SCLFAC
  385. CA = CA / SCLFAC
  386. R = R*SCLFAC
  387. RA = RA*SCLFAC
  388. END DO
  389. *
  390. * Now balance.
  391. *
  392. IF( ( C+R ).GE.FACTOR*S ) CYCLE
  393. IF( F.LT.ONE .AND. SCALE( I ).LT.ONE ) THEN
  394. IF( F*SCALE( I ).LE.SFMIN1 ) CYCLE
  395. END IF
  396. IF( F.GT.ONE .AND. SCALE( I ).GT.ONE ) THEN
  397. IF( SCALE( I ).GE.SFMAX1 / F ) CYCLE
  398. END IF
  399. G = ONE / F
  400. SCALE( I ) = SCALE( I )*F
  401. NOCONV = .TRUE.
  402. *
  403. CALL CSSCAL( N-K+1, G, A( I, K ), LDA )
  404. CALL CSSCAL( L, F, A( 1, I ), 1 )
  405. *
  406. END DO
  407. *
  408. END DO
  409. *
  410. ILO = K
  411. IHI = L
  412. *
  413. RETURN
  414. *
  415. * End of CGEBAL
  416. *
  417. END