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.

zgsvj0.f 36 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726727728729730731732733734735736737738739740741742743744745746747748749750751752753754755756757758759760761762763764765766767768769770771772773774775776777778779780781782783784785786787788789790791792793794795796797798799800801802803804805806807808809810811812813814815816817818819820821822823824825826827828829830831832833834835836837838839840841842843844845846847848849850851852853854855856857858859860861862863864865866867868869870871872873874875876877878879880881882883884885886887888889890891892893894895896897898899900901902903904905906907908909910911912913914915916917918919920921922923924925926927928929930931932933934935
  1. *> \brief <b> ZGSVJ0 pre-processor for the routine zgesvj. </b>
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download ZGSVJ0 + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zgsvj0.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zgsvj0.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zgsvj0.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE ZGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS,
  22. * SFMIN, TOL, NSWEEP, WORK, LWORK, INFO )
  23. *
  24. * .. Scalar Arguments ..
  25. * INTEGER INFO, LDA, LDV, LWORK, M, MV, N, NSWEEP
  26. * DOUBLE PRECISION EPS, SFMIN, TOL
  27. * CHARACTER*1 JOBV
  28. * ..
  29. * .. Array Arguments ..
  30. * COMPLEX*16 A( LDA, * ), D( N ), V( LDV, * ), WORK( LWORK )
  31. * DOUBLE PRECISION SVA( N )
  32. * ..
  33. *
  34. *
  35. *> \par Purpose:
  36. * =============
  37. *>
  38. *> \verbatim
  39. *>
  40. *> ZGSVJ0 is called from ZGESVJ as a pre-processor and that is its main
  41. *> purpose. It applies Jacobi rotations in the same way as ZGESVJ does, but
  42. *> it does not check convergence (stopping criterion). Few tuning
  43. *> parameters (marked by [TP]) are available for the implementer.
  44. *> \endverbatim
  45. *
  46. * Arguments:
  47. * ==========
  48. *
  49. *> \param[in] JOBV
  50. *> \verbatim
  51. *> JOBV is CHARACTER*1
  52. *> Specifies whether the output from this procedure is used
  53. *> to compute the matrix V:
  54. *> = 'V': the product of the Jacobi rotations is accumulated
  55. *> by postmulyiplying the N-by-N array V.
  56. *> (See the description of V.)
  57. *> = 'A': the product of the Jacobi rotations is accumulated
  58. *> by postmulyiplying the MV-by-N array V.
  59. *> (See the descriptions of MV and V.)
  60. *> = 'N': the Jacobi rotations are not accumulated.
  61. *> \endverbatim
  62. *>
  63. *> \param[in] M
  64. *> \verbatim
  65. *> M is INTEGER
  66. *> The number of rows of the input matrix A. M >= 0.
  67. *> \endverbatim
  68. *>
  69. *> \param[in] N
  70. *> \verbatim
  71. *> N is INTEGER
  72. *> The number of columns of the input matrix A.
  73. *> M >= N >= 0.
  74. *> \endverbatim
  75. *>
  76. *> \param[in,out] A
  77. *> \verbatim
  78. *> A is COMPLEX*16 array, dimension (LDA,N)
  79. *> On entry, M-by-N matrix A, such that A*diag(D) represents
  80. *> the input matrix.
  81. *> On exit,
  82. *> A_onexit * diag(D_onexit) represents the input matrix A*diag(D)
  83. *> post-multiplied by a sequence of Jacobi rotations, where the
  84. *> rotation threshold and the total number of sweeps are given in
  85. *> TOL and NSWEEP, respectively.
  86. *> (See the descriptions of D, TOL and NSWEEP.)
  87. *> \endverbatim
  88. *>
  89. *> \param[in] LDA
  90. *> \verbatim
  91. *> LDA is INTEGER
  92. *> The leading dimension of the array A. LDA >= max(1,M).
  93. *> \endverbatim
  94. *>
  95. *> \param[in,out] D
  96. *> \verbatim
  97. *> D is COMPLEX*16 array, dimension (N)
  98. *> The array D accumulates the scaling factors from the complex scaled
  99. *> Jacobi rotations.
  100. *> On entry, A*diag(D) represents the input matrix.
  101. *> On exit, A_onexit*diag(D_onexit) represents the input matrix
  102. *> post-multiplied by a sequence of Jacobi rotations, where the
  103. *> rotation threshold and the total number of sweeps are given in
  104. *> TOL and NSWEEP, respectively.
  105. *> (See the descriptions of A, TOL and NSWEEP.)
  106. *> \endverbatim
  107. *>
  108. *> \param[in,out] SVA
  109. *> \verbatim
  110. *> SVA is DOUBLE PRECISION array, dimension (N)
  111. *> On entry, SVA contains the Euclidean norms of the columns of
  112. *> the matrix A*diag(D).
  113. *> On exit, SVA contains the Euclidean norms of the columns of
  114. *> the matrix A_onexit*diag(D_onexit).
  115. *> \endverbatim
  116. *>
  117. *> \param[in] MV
  118. *> \verbatim
  119. *> MV is INTEGER
  120. *> If JOBV .EQ. 'A', then MV rows of V are post-multipled by a
  121. *> sequence of Jacobi rotations.
  122. *> If JOBV = 'N', then MV is not referenced.
  123. *> \endverbatim
  124. *>
  125. *> \param[in,out] V
  126. *> \verbatim
  127. *> V is COMPLEX*16 array, dimension (LDV,N)
  128. *> If JOBV .EQ. 'V' then N rows of V are post-multipled by a
  129. *> sequence of Jacobi rotations.
  130. *> If JOBV .EQ. 'A' then MV rows of V are post-multipled by a
  131. *> sequence of Jacobi rotations.
  132. *> If JOBV = 'N', then V is not referenced.
  133. *> \endverbatim
  134. *>
  135. *> \param[in] LDV
  136. *> \verbatim
  137. *> LDV is INTEGER
  138. *> The leading dimension of the array V, LDV >= 1.
  139. *> If JOBV = 'V', LDV .GE. N.
  140. *> If JOBV = 'A', LDV .GE. MV.
  141. *> \endverbatim
  142. *>
  143. *> \param[in] EPS
  144. *> \verbatim
  145. *> EPS is DOUBLE PRECISION
  146. *> EPS = DLAMCH('Epsilon')
  147. *> \endverbatim
  148. *>
  149. *> \param[in] SFMIN
  150. *> \verbatim
  151. *> SFMIN is DOUBLE PRECISION
  152. *> SFMIN = DLAMCH('Safe Minimum')
  153. *> \endverbatim
  154. *>
  155. *> \param[in] TOL
  156. *> \verbatim
  157. *> TOL is DOUBLE PRECISION
  158. *> TOL is the threshold for Jacobi rotations. For a pair
  159. *> A(:,p), A(:,q) of pivot columns, the Jacobi rotation is
  160. *> applied only if ABS(COS(angle(A(:,p),A(:,q)))) .GT. TOL.
  161. *> \endverbatim
  162. *>
  163. *> \param[in] NSWEEP
  164. *> \verbatim
  165. *> NSWEEP is INTEGER
  166. *> NSWEEP is the number of sweeps of Jacobi rotations to be
  167. *> performed.
  168. *> \endverbatim
  169. *>
  170. *> \param[out] WORK
  171. *> \verbatim
  172. *> WORK is COMPLEX*16 array, dimension (LWORK)
  173. *> \endverbatim
  174. *>
  175. *> \param[in] LWORK
  176. *> \verbatim
  177. *> LWORK is INTEGER
  178. *> LWORK is the dimension of WORK. LWORK .GE. M.
  179. *> \endverbatim
  180. *>
  181. *> \param[out] INFO
  182. *> \verbatim
  183. *> INFO is INTEGER
  184. *> = 0 : successful exit.
  185. *> < 0 : if INFO = -i, then the i-th argument had an illegal value
  186. *> \endverbatim
  187. *
  188. * Authors:
  189. * ========
  190. *
  191. *> \author Univ. of Tennessee
  192. *> \author Univ. of California Berkeley
  193. *> \author Univ. of Colorado Denver
  194. *> \author NAG Ltd.
  195. *
  196. *> \date June 2016
  197. *
  198. *> \ingroup complex16OTHERcomputational
  199. *>
  200. *> \par Further Details:
  201. * =====================
  202. *>
  203. *> ZGSVJ0 is used just to enable ZGESVJ to call a simplified version of
  204. *> itself to work on a submatrix of the original matrix.
  205. *>
  206. *> Contributor:
  207. * =============
  208. *>
  209. *> Zlatko Drmac (Zagreb, Croatia)
  210. *>
  211. *> \par Bugs, Examples and Comments:
  212. * ============================
  213. *>
  214. *> Please report all bugs and send interesting test examples and comments to
  215. *> drmac@math.hr. Thank you.
  216. *
  217. * =====================================================================
  218. SUBROUTINE ZGSVJ0( JOBV, M, N, A, LDA, D, SVA, MV, V, LDV, EPS,
  219. $ SFMIN, TOL, NSWEEP, WORK, LWORK, INFO )
  220. *
  221. * -- LAPACK computational routine (version 3.8.0) --
  222. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  223. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  224. * June 2016
  225. *
  226. IMPLICIT NONE
  227. * .. Scalar Arguments ..
  228. INTEGER INFO, LDA, LDV, LWORK, M, MV, N, NSWEEP
  229. DOUBLE PRECISION EPS, SFMIN, TOL
  230. CHARACTER*1 JOBV
  231. * ..
  232. * .. Array Arguments ..
  233. COMPLEX*16 A( LDA, * ), D( N ), V( LDV, * ), WORK( LWORK )
  234. DOUBLE PRECISION SVA( N )
  235. * ..
  236. *
  237. * =====================================================================
  238. *
  239. * .. Local Parameters ..
  240. DOUBLE PRECISION ZERO, HALF, ONE
  241. PARAMETER ( ZERO = 0.0D0, HALF = 0.5D0, ONE = 1.0D0)
  242. COMPLEX*16 CZERO, CONE
  243. PARAMETER ( CZERO = (0.0D0, 0.0D0), CONE = (1.0D0, 0.0D0) )
  244. * ..
  245. * .. Local Scalars ..
  246. COMPLEX*16 AAPQ, OMPQ
  247. DOUBLE PRECISION AAPP, AAPP0, AAPQ1, AAQQ, APOAQ, AQOAP, BIG,
  248. $ BIGTHETA, CS, MXAAPQ, MXSINJ, ROOTBIG, ROOTEPS,
  249. $ ROOTSFMIN, ROOTTOL, SMALL, SN, T, TEMP1, THETA,
  250. $ THSIGN
  251. INTEGER BLSKIP, EMPTSW, i, ibr, IERR, igl, IJBLSK, ir1,
  252. $ ISWROT, jbc, jgl, KBL, LKAHEAD, MVL, NBL,
  253. $ NOTROT, p, PSKIPPED, q, ROWSKIP, SWBAND
  254. LOGICAL APPLV, ROTOK, RSVEC
  255. * ..
  256. * ..
  257. * .. Intrinsic Functions ..
  258. INTRINSIC ABS, MAX, CONJG, DBLE, MIN, SIGN, SQRT
  259. * ..
  260. * .. External Functions ..
  261. DOUBLE PRECISION DZNRM2
  262. COMPLEX*16 ZDOTC
  263. INTEGER IDAMAX
  264. LOGICAL LSAME
  265. EXTERNAL IDAMAX, LSAME, ZDOTC, DZNRM2
  266. * ..
  267. * ..
  268. * .. External Subroutines ..
  269. * ..
  270. * from BLAS
  271. EXTERNAL ZCOPY, ZROT, ZSWAP, ZAXPY
  272. * from LAPACK
  273. EXTERNAL ZLASCL, ZLASSQ, XERBLA
  274. * ..
  275. * .. Executable Statements ..
  276. *
  277. * Test the input parameters.
  278. *
  279. APPLV = LSAME( JOBV, 'A' )
  280. RSVEC = LSAME( JOBV, 'V' )
  281. IF( .NOT.( RSVEC .OR. APPLV .OR. LSAME( JOBV, 'N' ) ) ) THEN
  282. INFO = -1
  283. ELSE IF( M.LT.0 ) THEN
  284. INFO = -2
  285. ELSE IF( ( N.LT.0 ) .OR. ( N.GT.M ) ) THEN
  286. INFO = -3
  287. ELSE IF( LDA.LT.M ) THEN
  288. INFO = -5
  289. ELSE IF( ( RSVEC.OR.APPLV ) .AND. ( MV.LT.0 ) ) THEN
  290. INFO = -8
  291. ELSE IF( ( RSVEC.AND.( LDV.LT.N ) ).OR.
  292. $ ( APPLV.AND.( LDV.LT.MV ) ) ) THEN
  293. INFO = -10
  294. ELSE IF( TOL.LE.EPS ) THEN
  295. INFO = -13
  296. ELSE IF( NSWEEP.LT.0 ) THEN
  297. INFO = -14
  298. ELSE IF( LWORK.LT.M ) THEN
  299. INFO = -16
  300. ELSE
  301. INFO = 0
  302. END IF
  303. *
  304. * #:(
  305. IF( INFO.NE.0 ) THEN
  306. CALL XERBLA( 'ZGSVJ0', -INFO )
  307. RETURN
  308. END IF
  309. *
  310. IF( RSVEC ) THEN
  311. MVL = N
  312. ELSE IF( APPLV ) THEN
  313. MVL = MV
  314. END IF
  315. RSVEC = RSVEC .OR. APPLV
  316. ROOTEPS = SQRT( EPS )
  317. ROOTSFMIN = SQRT( SFMIN )
  318. SMALL = SFMIN / EPS
  319. BIG = ONE / SFMIN
  320. ROOTBIG = ONE / ROOTSFMIN
  321. BIGTHETA = ONE / ROOTEPS
  322. ROOTTOL = SQRT( TOL )
  323. *
  324. * .. Row-cyclic Jacobi SVD algorithm with column pivoting ..
  325. *
  326. EMPTSW = ( N*( N-1 ) ) / 2
  327. NOTROT = 0
  328. *
  329. * .. Row-cyclic pivot strategy with de Rijk's pivoting ..
  330. *
  331. SWBAND = 0
  332. *[TP] SWBAND is a tuning parameter [TP]. It is meaningful and effective
  333. * if ZGESVJ is used as a computational routine in the preconditioned
  334. * Jacobi SVD algorithm ZGEJSV. For sweeps i=1:SWBAND the procedure
  335. * works on pivots inside a band-like region around the diagonal.
  336. * The boundaries are determined dynamically, based on the number of
  337. * pivots above a threshold.
  338. *
  339. KBL = MIN( 8, N )
  340. *[TP] KBL is a tuning parameter that defines the tile size in the
  341. * tiling of the p-q loops of pivot pairs. In general, an optimal
  342. * value of KBL depends on the matrix dimensions and on the
  343. * parameters of the computer's memory.
  344. *
  345. NBL = N / KBL
  346. IF( ( NBL*KBL ).NE.N )NBL = NBL + 1
  347. *
  348. BLSKIP = KBL**2
  349. *[TP] BLKSKIP is a tuning parameter that depends on SWBAND and KBL.
  350. *
  351. ROWSKIP = MIN( 5, KBL )
  352. *[TP] ROWSKIP is a tuning parameter.
  353. *
  354. LKAHEAD = 1
  355. *[TP] LKAHEAD is a tuning parameter.
  356. *
  357. * Quasi block transformations, using the lower (upper) triangular
  358. * structure of the input matrix. The quasi-block-cycling usually
  359. * invokes cubic convergence. Big part of this cycle is done inside
  360. * canonical subspaces of dimensions less than M.
  361. *
  362. *
  363. * .. Row-cyclic pivot strategy with de Rijk's pivoting ..
  364. *
  365. DO 1993 i = 1, NSWEEP
  366. *
  367. * .. go go go ...
  368. *
  369. MXAAPQ = ZERO
  370. MXSINJ = ZERO
  371. ISWROT = 0
  372. *
  373. NOTROT = 0
  374. PSKIPPED = 0
  375. *
  376. * Each sweep is unrolled using KBL-by-KBL tiles over the pivot pairs
  377. * 1 <= p < q <= N. This is the first step toward a blocked implementation
  378. * of the rotations. New implementation, based on block transformations,
  379. * is under development.
  380. *
  381. DO 2000 ibr = 1, NBL
  382. *
  383. igl = ( ibr-1 )*KBL + 1
  384. *
  385. DO 1002 ir1 = 0, MIN( LKAHEAD, NBL-ibr )
  386. *
  387. igl = igl + ir1*KBL
  388. *
  389. DO 2001 p = igl, MIN( igl+KBL-1, N-1 )
  390. *
  391. * .. de Rijk's pivoting
  392. *
  393. q = IDAMAX( N-p+1, SVA( p ), 1 ) + p - 1
  394. IF( p.NE.q ) THEN
  395. CALL ZSWAP( M, A( 1, p ), 1, A( 1, q ), 1 )
  396. IF( RSVEC )CALL ZSWAP( MVL, V( 1, p ), 1,
  397. $ V( 1, q ), 1 )
  398. TEMP1 = SVA( p )
  399. SVA( p ) = SVA( q )
  400. SVA( q ) = TEMP1
  401. AAPQ = D(p)
  402. D(p) = D(q)
  403. D(q) = AAPQ
  404. END IF
  405. *
  406. IF( ir1.EQ.0 ) THEN
  407. *
  408. * Column norms are periodically updated by explicit
  409. * norm computation.
  410. * Caveat:
  411. * Unfortunately, some BLAS implementations compute SNCRM2(M,A(1,p),1)
  412. * as SQRT(S=ZDOTC(M,A(1,p),1,A(1,p),1)), which may cause the result to
  413. * overflow for ||A(:,p)||_2 > SQRT(overflow_threshold), and to
  414. * underflow for ||A(:,p)||_2 < SQRT(underflow_threshold).
  415. * Hence, DZNRM2 cannot be trusted, not even in the case when
  416. * the true norm is far from the under(over)flow boundaries.
  417. * If properly implemented DZNRM2 is available, the IF-THEN-ELSE-END IF
  418. * below should be replaced with "AAPP = DZNRM2( M, A(1,p), 1 )".
  419. *
  420. IF( ( SVA( p ).LT.ROOTBIG ) .AND.
  421. $ ( SVA( p ).GT.ROOTSFMIN ) ) THEN
  422. SVA( p ) = DZNRM2( M, A( 1, p ), 1 )
  423. ELSE
  424. TEMP1 = ZERO
  425. AAPP = ONE
  426. CALL ZLASSQ( M, A( 1, p ), 1, TEMP1, AAPP )
  427. SVA( p ) = TEMP1*SQRT( AAPP )
  428. END IF
  429. AAPP = SVA( p )
  430. ELSE
  431. AAPP = SVA( p )
  432. END IF
  433. *
  434. IF( AAPP.GT.ZERO ) THEN
  435. *
  436. PSKIPPED = 0
  437. *
  438. DO 2002 q = p + 1, MIN( igl+KBL-1, N )
  439. *
  440. AAQQ = SVA( q )
  441. *
  442. IF( AAQQ.GT.ZERO ) THEN
  443. *
  444. AAPP0 = AAPP
  445. IF( AAQQ.GE.ONE ) THEN
  446. ROTOK = ( SMALL*AAPP ).LE.AAQQ
  447. IF( AAPP.LT.( BIG / AAQQ ) ) THEN
  448. AAPQ = ( ZDOTC( M, A( 1, p ), 1,
  449. $ A( 1, q ), 1 ) / AAQQ ) / AAPP
  450. ELSE
  451. CALL ZCOPY( M, A( 1, p ), 1,
  452. $ WORK, 1 )
  453. CALL ZLASCL( 'G', 0, 0, AAPP, ONE,
  454. $ M, 1, WORK, LDA, IERR )
  455. AAPQ = ZDOTC( M, WORK, 1,
  456. $ A( 1, q ), 1 ) / AAQQ
  457. END IF
  458. ELSE
  459. ROTOK = AAPP.LE.( AAQQ / SMALL )
  460. IF( AAPP.GT.( SMALL / AAQQ ) ) THEN
  461. AAPQ = ( ZDOTC( M, A( 1, p ), 1,
  462. $ A( 1, q ), 1 ) / AAPP ) / AAQQ
  463. ELSE
  464. CALL ZCOPY( M, A( 1, q ), 1,
  465. $ WORK, 1 )
  466. CALL ZLASCL( 'G', 0, 0, AAQQ,
  467. $ ONE, M, 1,
  468. $ WORK, LDA, IERR )
  469. AAPQ = ZDOTC( M, A( 1, p ), 1,
  470. $ WORK, 1 ) / AAPP
  471. END IF
  472. END IF
  473. *
  474. * AAPQ = AAPQ * CONJG( CWORK(p) ) * CWORK(q)
  475. AAPQ1 = -ABS(AAPQ)
  476. MXAAPQ = MAX( MXAAPQ, -AAPQ1 )
  477. *
  478. * TO rotate or NOT to rotate, THAT is the question ...
  479. *
  480. IF( ABS( AAPQ1 ).GT.TOL ) THEN
  481. OMPQ = AAPQ / ABS(AAPQ)
  482. *
  483. * .. rotate
  484. *[RTD] ROTATED = ROTATED + ONE
  485. *
  486. IF( ir1.EQ.0 ) THEN
  487. NOTROT = 0
  488. PSKIPPED = 0
  489. ISWROT = ISWROT + 1
  490. END IF
  491. *
  492. IF( ROTOK ) THEN
  493. *
  494. AQOAP = AAQQ / AAPP
  495. APOAQ = AAPP / AAQQ
  496. THETA = -HALF*ABS( AQOAP-APOAQ )/AAPQ1
  497. *
  498. IF( ABS( THETA ).GT.BIGTHETA ) THEN
  499. *
  500. T = HALF / THETA
  501. CS = ONE
  502. CALL ZROT( M, A(1,p), 1, A(1,q), 1,
  503. $ CS, CONJG(OMPQ)*T )
  504. IF ( RSVEC ) THEN
  505. CALL ZROT( MVL, V(1,p), 1,
  506. $ V(1,q), 1, CS, CONJG(OMPQ)*T )
  507. END IF
  508. SVA( q ) = AAQQ*SQRT( MAX( ZERO,
  509. $ ONE+T*APOAQ*AAPQ1 ) )
  510. AAPP = AAPP*SQRT( MAX( ZERO,
  511. $ ONE-T*AQOAP*AAPQ1 ) )
  512. MXSINJ = MAX( MXSINJ, ABS( T ) )
  513. *
  514. ELSE
  515. *
  516. * .. choose correct signum for THETA and rotate
  517. *
  518. THSIGN = -SIGN( ONE, AAPQ1 )
  519. T = ONE / ( THETA+THSIGN*
  520. $ SQRT( ONE+THETA*THETA ) )
  521. CS = SQRT( ONE / ( ONE+T*T ) )
  522. SN = T*CS
  523. *
  524. MXSINJ = MAX( MXSINJ, ABS( SN ) )
  525. SVA( q ) = AAQQ*SQRT( MAX( ZERO,
  526. $ ONE+T*APOAQ*AAPQ1 ) )
  527. AAPP = AAPP*SQRT( MAX( ZERO,
  528. $ ONE-T*AQOAP*AAPQ1 ) )
  529. *
  530. CALL ZROT( M, A(1,p), 1, A(1,q), 1,
  531. $ CS, CONJG(OMPQ)*SN )
  532. IF ( RSVEC ) THEN
  533. CALL ZROT( MVL, V(1,p), 1,
  534. $ V(1,q), 1, CS, CONJG(OMPQ)*SN )
  535. END IF
  536. END IF
  537. D(p) = -D(q) * OMPQ
  538. *
  539. ELSE
  540. * .. have to use modified Gram-Schmidt like transformation
  541. CALL ZCOPY( M, A( 1, p ), 1,
  542. $ WORK, 1 )
  543. CALL ZLASCL( 'G', 0, 0, AAPP, ONE, M,
  544. $ 1, WORK, LDA,
  545. $ IERR )
  546. CALL ZLASCL( 'G', 0, 0, AAQQ, ONE, M,
  547. $ 1, A( 1, q ), LDA, IERR )
  548. CALL ZAXPY( M, -AAPQ, WORK, 1,
  549. $ A( 1, q ), 1 )
  550. CALL ZLASCL( 'G', 0, 0, ONE, AAQQ, M,
  551. $ 1, A( 1, q ), LDA, IERR )
  552. SVA( q ) = AAQQ*SQRT( MAX( ZERO,
  553. $ ONE-AAPQ1*AAPQ1 ) )
  554. MXSINJ = MAX( MXSINJ, SFMIN )
  555. END IF
  556. * END IF ROTOK THEN ... ELSE
  557. *
  558. * In the case of cancellation in updating SVA(q), SVA(p)
  559. * recompute SVA(q), SVA(p).
  560. *
  561. IF( ( SVA( q ) / AAQQ )**2.LE.ROOTEPS )
  562. $ THEN
  563. IF( ( AAQQ.LT.ROOTBIG ) .AND.
  564. $ ( AAQQ.GT.ROOTSFMIN ) ) THEN
  565. SVA( q ) = DZNRM2( M, A( 1, q ), 1 )
  566. ELSE
  567. T = ZERO
  568. AAQQ = ONE
  569. CALL ZLASSQ( M, A( 1, q ), 1, T,
  570. $ AAQQ )
  571. SVA( q ) = T*SQRT( AAQQ )
  572. END IF
  573. END IF
  574. IF( ( AAPP / AAPP0 ).LE.ROOTEPS ) THEN
  575. IF( ( AAPP.LT.ROOTBIG ) .AND.
  576. $ ( AAPP.GT.ROOTSFMIN ) ) THEN
  577. AAPP = DZNRM2( M, A( 1, p ), 1 )
  578. ELSE
  579. T = ZERO
  580. AAPP = ONE
  581. CALL ZLASSQ( M, A( 1, p ), 1, T,
  582. $ AAPP )
  583. AAPP = T*SQRT( AAPP )
  584. END IF
  585. SVA( p ) = AAPP
  586. END IF
  587. *
  588. ELSE
  589. * A(:,p) and A(:,q) already numerically orthogonal
  590. IF( ir1.EQ.0 )NOTROT = NOTROT + 1
  591. *[RTD] SKIPPED = SKIPPED + 1
  592. PSKIPPED = PSKIPPED + 1
  593. END IF
  594. ELSE
  595. * A(:,q) is zero column
  596. IF( ir1.EQ.0 )NOTROT = NOTROT + 1
  597. PSKIPPED = PSKIPPED + 1
  598. END IF
  599. *
  600. IF( ( i.LE.SWBAND ) .AND.
  601. $ ( PSKIPPED.GT.ROWSKIP ) ) THEN
  602. IF( ir1.EQ.0 )AAPP = -AAPP
  603. NOTROT = 0
  604. GO TO 2103
  605. END IF
  606. *
  607. 2002 CONTINUE
  608. * END q-LOOP
  609. *
  610. 2103 CONTINUE
  611. * bailed out of q-loop
  612. *
  613. SVA( p ) = AAPP
  614. *
  615. ELSE
  616. SVA( p ) = AAPP
  617. IF( ( ir1.EQ.0 ) .AND. ( AAPP.EQ.ZERO ) )
  618. $ NOTROT = NOTROT + MIN( igl+KBL-1, N ) - p
  619. END IF
  620. *
  621. 2001 CONTINUE
  622. * end of the p-loop
  623. * end of doing the block ( ibr, ibr )
  624. 1002 CONTINUE
  625. * end of ir1-loop
  626. *
  627. * ... go to the off diagonal blocks
  628. *
  629. igl = ( ibr-1 )*KBL + 1
  630. *
  631. DO 2010 jbc = ibr + 1, NBL
  632. *
  633. jgl = ( jbc-1 )*KBL + 1
  634. *
  635. * doing the block at ( ibr, jbc )
  636. *
  637. IJBLSK = 0
  638. DO 2100 p = igl, MIN( igl+KBL-1, N )
  639. *
  640. AAPP = SVA( p )
  641. IF( AAPP.GT.ZERO ) THEN
  642. *
  643. PSKIPPED = 0
  644. *
  645. DO 2200 q = jgl, MIN( jgl+KBL-1, N )
  646. *
  647. AAQQ = SVA( q )
  648. IF( AAQQ.GT.ZERO ) THEN
  649. AAPP0 = AAPP
  650. *
  651. * .. M x 2 Jacobi SVD ..
  652. *
  653. * Safe Gram matrix computation
  654. *
  655. IF( AAQQ.GE.ONE ) THEN
  656. IF( AAPP.GE.AAQQ ) THEN
  657. ROTOK = ( SMALL*AAPP ).LE.AAQQ
  658. ELSE
  659. ROTOK = ( SMALL*AAQQ ).LE.AAPP
  660. END IF
  661. IF( AAPP.LT.( BIG / AAQQ ) ) THEN
  662. AAPQ = ( ZDOTC( M, A( 1, p ), 1,
  663. $ A( 1, q ), 1 ) / AAQQ ) / AAPP
  664. ELSE
  665. CALL ZCOPY( M, A( 1, p ), 1,
  666. $ WORK, 1 )
  667. CALL ZLASCL( 'G', 0, 0, AAPP,
  668. $ ONE, M, 1,
  669. $ WORK, LDA, IERR )
  670. AAPQ = ZDOTC( M, WORK, 1,
  671. $ A( 1, q ), 1 ) / AAQQ
  672. END IF
  673. ELSE
  674. IF( AAPP.GE.AAQQ ) THEN
  675. ROTOK = AAPP.LE.( AAQQ / SMALL )
  676. ELSE
  677. ROTOK = AAQQ.LE.( AAPP / SMALL )
  678. END IF
  679. IF( AAPP.GT.( SMALL / AAQQ ) ) THEN
  680. AAPQ = ( ZDOTC( M, A( 1, p ), 1,
  681. $ A( 1, q ), 1 ) / MAX(AAQQ,AAPP) )
  682. $ / MIN(AAQQ,AAPP)
  683. ELSE
  684. CALL ZCOPY( M, A( 1, q ), 1,
  685. $ WORK, 1 )
  686. CALL ZLASCL( 'G', 0, 0, AAQQ,
  687. $ ONE, M, 1,
  688. $ WORK, LDA, IERR )
  689. AAPQ = ZDOTC( M, A( 1, p ), 1,
  690. $ WORK, 1 ) / AAPP
  691. END IF
  692. END IF
  693. *
  694. * AAPQ = AAPQ * CONJG(CWORK(p))*CWORK(q)
  695. AAPQ1 = -ABS(AAPQ)
  696. MXAAPQ = MAX( MXAAPQ, -AAPQ1 )
  697. *
  698. * TO rotate or NOT to rotate, THAT is the question ...
  699. *
  700. IF( ABS( AAPQ1 ).GT.TOL ) THEN
  701. OMPQ = AAPQ / ABS(AAPQ)
  702. NOTROT = 0
  703. *[RTD] ROTATED = ROTATED + 1
  704. PSKIPPED = 0
  705. ISWROT = ISWROT + 1
  706. *
  707. IF( ROTOK ) THEN
  708. *
  709. AQOAP = AAQQ / AAPP
  710. APOAQ = AAPP / AAQQ
  711. THETA = -HALF*ABS( AQOAP-APOAQ )/ AAPQ1
  712. IF( AAQQ.GT.AAPP0 )THETA = -THETA
  713. *
  714. IF( ABS( THETA ).GT.BIGTHETA ) THEN
  715. T = HALF / THETA
  716. CS = ONE
  717. CALL ZROT( M, A(1,p), 1, A(1,q), 1,
  718. $ CS, CONJG(OMPQ)*T )
  719. IF( RSVEC ) THEN
  720. CALL ZROT( MVL, V(1,p), 1,
  721. $ V(1,q), 1, CS, CONJG(OMPQ)*T )
  722. END IF
  723. SVA( q ) = AAQQ*SQRT( MAX( ZERO,
  724. $ ONE+T*APOAQ*AAPQ1 ) )
  725. AAPP = AAPP*SQRT( MAX( ZERO,
  726. $ ONE-T*AQOAP*AAPQ1 ) )
  727. MXSINJ = MAX( MXSINJ, ABS( T ) )
  728. ELSE
  729. *
  730. * .. choose correct signum for THETA and rotate
  731. *
  732. THSIGN = -SIGN( ONE, AAPQ1 )
  733. IF( AAQQ.GT.AAPP0 )THSIGN = -THSIGN
  734. T = ONE / ( THETA+THSIGN*
  735. $ SQRT( ONE+THETA*THETA ) )
  736. CS = SQRT( ONE / ( ONE+T*T ) )
  737. SN = T*CS
  738. MXSINJ = MAX( MXSINJ, ABS( SN ) )
  739. SVA( q ) = AAQQ*SQRT( MAX( ZERO,
  740. $ ONE+T*APOAQ*AAPQ1 ) )
  741. AAPP = AAPP*SQRT( MAX( ZERO,
  742. $ ONE-T*AQOAP*AAPQ1 ) )
  743. *
  744. CALL ZROT( M, A(1,p), 1, A(1,q), 1,
  745. $ CS, CONJG(OMPQ)*SN )
  746. IF( RSVEC ) THEN
  747. CALL ZROT( MVL, V(1,p), 1,
  748. $ V(1,q), 1, CS, CONJG(OMPQ)*SN )
  749. END IF
  750. END IF
  751. D(p) = -D(q) * OMPQ
  752. *
  753. ELSE
  754. * .. have to use modified Gram-Schmidt like transformation
  755. IF( AAPP.GT.AAQQ ) THEN
  756. CALL ZCOPY( M, A( 1, p ), 1,
  757. $ WORK, 1 )
  758. CALL ZLASCL( 'G', 0, 0, AAPP, ONE,
  759. $ M, 1, WORK,LDA,
  760. $ IERR )
  761. CALL ZLASCL( 'G', 0, 0, AAQQ, ONE,
  762. $ M, 1, A( 1, q ), LDA,
  763. $ IERR )
  764. CALL ZAXPY( M, -AAPQ, WORK,
  765. $ 1, A( 1, q ), 1 )
  766. CALL ZLASCL( 'G', 0, 0, ONE, AAQQ,
  767. $ M, 1, A( 1, q ), LDA,
  768. $ IERR )
  769. SVA( q ) = AAQQ*SQRT( MAX( ZERO,
  770. $ ONE-AAPQ1*AAPQ1 ) )
  771. MXSINJ = MAX( MXSINJ, SFMIN )
  772. ELSE
  773. CALL ZCOPY( M, A( 1, q ), 1,
  774. $ WORK, 1 )
  775. CALL ZLASCL( 'G', 0, 0, AAQQ, ONE,
  776. $ M, 1, WORK,LDA,
  777. $ IERR )
  778. CALL ZLASCL( 'G', 0, 0, AAPP, ONE,
  779. $ M, 1, A( 1, p ), LDA,
  780. $ IERR )
  781. CALL ZAXPY( M, -CONJG(AAPQ),
  782. $ WORK, 1, A( 1, p ), 1 )
  783. CALL ZLASCL( 'G', 0, 0, ONE, AAPP,
  784. $ M, 1, A( 1, p ), LDA,
  785. $ IERR )
  786. SVA( p ) = AAPP*SQRT( MAX( ZERO,
  787. $ ONE-AAPQ1*AAPQ1 ) )
  788. MXSINJ = MAX( MXSINJ, SFMIN )
  789. END IF
  790. END IF
  791. * END IF ROTOK THEN ... ELSE
  792. *
  793. * In the case of cancellation in updating SVA(q), SVA(p)
  794. * .. recompute SVA(q), SVA(p)
  795. IF( ( SVA( q ) / AAQQ )**2.LE.ROOTEPS )
  796. $ THEN
  797. IF( ( AAQQ.LT.ROOTBIG ) .AND.
  798. $ ( AAQQ.GT.ROOTSFMIN ) ) THEN
  799. SVA( q ) = DZNRM2( M, A( 1, q ), 1)
  800. ELSE
  801. T = ZERO
  802. AAQQ = ONE
  803. CALL ZLASSQ( M, A( 1, q ), 1, T,
  804. $ AAQQ )
  805. SVA( q ) = T*SQRT( AAQQ )
  806. END IF
  807. END IF
  808. IF( ( AAPP / AAPP0 )**2.LE.ROOTEPS ) THEN
  809. IF( ( AAPP.LT.ROOTBIG ) .AND.
  810. $ ( AAPP.GT.ROOTSFMIN ) ) THEN
  811. AAPP = DZNRM2( M, A( 1, p ), 1 )
  812. ELSE
  813. T = ZERO
  814. AAPP = ONE
  815. CALL ZLASSQ( M, A( 1, p ), 1, T,
  816. $ AAPP )
  817. AAPP = T*SQRT( AAPP )
  818. END IF
  819. SVA( p ) = AAPP
  820. END IF
  821. * end of OK rotation
  822. ELSE
  823. NOTROT = NOTROT + 1
  824. *[RTD] SKIPPED = SKIPPED + 1
  825. PSKIPPED = PSKIPPED + 1
  826. IJBLSK = IJBLSK + 1
  827. END IF
  828. ELSE
  829. NOTROT = NOTROT + 1
  830. PSKIPPED = PSKIPPED + 1
  831. IJBLSK = IJBLSK + 1
  832. END IF
  833. *
  834. IF( ( i.LE.SWBAND ) .AND. ( IJBLSK.GE.BLSKIP ) )
  835. $ THEN
  836. SVA( p ) = AAPP
  837. NOTROT = 0
  838. GO TO 2011
  839. END IF
  840. IF( ( i.LE.SWBAND ) .AND.
  841. $ ( PSKIPPED.GT.ROWSKIP ) ) THEN
  842. AAPP = -AAPP
  843. NOTROT = 0
  844. GO TO 2203
  845. END IF
  846. *
  847. 2200 CONTINUE
  848. * end of the q-loop
  849. 2203 CONTINUE
  850. *
  851. SVA( p ) = AAPP
  852. *
  853. ELSE
  854. *
  855. IF( AAPP.EQ.ZERO )NOTROT = NOTROT +
  856. $ MIN( jgl+KBL-1, N ) - jgl + 1
  857. IF( AAPP.LT.ZERO )NOTROT = 0
  858. *
  859. END IF
  860. *
  861. 2100 CONTINUE
  862. * end of the p-loop
  863. 2010 CONTINUE
  864. * end of the jbc-loop
  865. 2011 CONTINUE
  866. *2011 bailed out of the jbc-loop
  867. DO 2012 p = igl, MIN( igl+KBL-1, N )
  868. SVA( p ) = ABS( SVA( p ) )
  869. 2012 CONTINUE
  870. ***
  871. 2000 CONTINUE
  872. *2000 :: end of the ibr-loop
  873. *
  874. * .. update SVA(N)
  875. IF( ( SVA( N ).LT.ROOTBIG ) .AND. ( SVA( N ).GT.ROOTSFMIN ) )
  876. $ THEN
  877. SVA( N ) = DZNRM2( M, A( 1, N ), 1 )
  878. ELSE
  879. T = ZERO
  880. AAPP = ONE
  881. CALL ZLASSQ( M, A( 1, N ), 1, T, AAPP )
  882. SVA( N ) = T*SQRT( AAPP )
  883. END IF
  884. *
  885. * Additional steering devices
  886. *
  887. IF( ( i.LT.SWBAND ) .AND. ( ( MXAAPQ.LE.ROOTTOL ) .OR.
  888. $ ( ISWROT.LE.N ) ) )SWBAND = i
  889. *
  890. IF( ( i.GT.SWBAND+1 ) .AND. ( MXAAPQ.LT.SQRT( DBLE( N ) )*
  891. $ TOL ) .AND. ( DBLE( N )*MXAAPQ*MXSINJ.LT.TOL ) ) THEN
  892. GO TO 1994
  893. END IF
  894. *
  895. IF( NOTROT.GE.EMPTSW )GO TO 1994
  896. *
  897. 1993 CONTINUE
  898. * end i=1:NSWEEP loop
  899. *
  900. * #:( Reaching this point means that the procedure has not converged.
  901. INFO = NSWEEP - 1
  902. GO TO 1995
  903. *
  904. 1994 CONTINUE
  905. * #:) Reaching this point means numerical convergence after the i-th
  906. * sweep.
  907. *
  908. INFO = 0
  909. * #:) INFO = 0 confirms successful iterations.
  910. 1995 CONTINUE
  911. *
  912. * Sort the vector SVA() of column norms.
  913. DO 5991 p = 1, N - 1
  914. q = IDAMAX( N-p+1, SVA( p ), 1 ) + p - 1
  915. IF( p.NE.q ) THEN
  916. TEMP1 = SVA( p )
  917. SVA( p ) = SVA( q )
  918. SVA( q ) = TEMP1
  919. AAPQ = D( p )
  920. D( p ) = D( q )
  921. D( q ) = AAPQ
  922. CALL ZSWAP( M, A( 1, p ), 1, A( 1, q ), 1 )
  923. IF( RSVEC )CALL ZSWAP( MVL, V( 1, p ), 1, V( 1, q ), 1 )
  924. END IF
  925. 5991 CONTINUE
  926. *
  927. RETURN
  928. * ..
  929. * .. END OF ZGSVJ0
  930. * ..
  931. END