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

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