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.

zlahef.f 23 kB

123456789101112131415161718192021222324252627282930313233343536373839404142434445464748495051525354555657585960616263646566676869707172737475767778798081828384858687888990919293949596979899100101102103104105106107108109110111112113114115116117118119120121122123124125126127128129130131132133134135136137138139140141142143144145146147148149150151152153154155156157158159160161162163164165166167168169170171172173174175176177178179180181182183184185186187188189190191192193194195196197198199200201202203204205206207208209210211212213214215216217218219220221222223224225226227228229230231232233234235236237238239240241242243244245246247248249250251252253254255256257258259260261262263264265266267268269270271272273274275276277278279280281282283284285286287288289290291292293294295296297298299300301302303304305306307308309310311312313314315316317318319320321322323324325326327328329330331332333334335336337338339340341342343344345346347348349350351352353354355356357358359360361362363364365366367368369370371372373374375376377378379380381382383384385386387388389390391392393394395396397398399400401402403404405406407408409410411412413414415416417418419420421422423424425426427428429430431432433434435436437438439440441442443444445446447448449450451452453454455456457458459460461462463464465466467468469470471472473474475476477478479480481482483484485486487488489490491492493494495496497498499500501502503504505506507508509510511512513514515516517518519520521522523524525526527528529530531532533534535536537538539540541542543544545546547548549550551552553554555556557558559560561562563564565566567568569570571572573574575576577578579580581582583584585586587588589590591592593594595596597598599600601602603604605606607608609610611612613614615616617618619620621622623624625626627628629630631632633634635636637638639640641642643644645646647648649650651652653654655656657658659660661662663664665666667668669670671672673674675676677678679680681682683684685686687688689690691692693694695696697698699700701702703704705706707708709710711712713714715716717718719720721722723724725726
  1. *> \brief \b ZLAHEF computes a partial factorization of a complex Hermitian indefinite matrix, using the diagonal pivoting method.
  2. *
  3. * =========== DOCUMENTATION ===========
  4. *
  5. * Online html documentation available at
  6. * http://www.netlib.org/lapack/explore-html/
  7. *
  8. *> \htmlonly
  9. *> Download ZLAHEF + dependencies
  10. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlahef.f">
  11. *> [TGZ]</a>
  12. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlahef.f">
  13. *> [ZIP]</a>
  14. *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlahef.f">
  15. *> [TXT]</a>
  16. *> \endhtmlonly
  17. *
  18. * Definition:
  19. * ===========
  20. *
  21. * SUBROUTINE ZLAHEF( UPLO, N, NB, KB, A, LDA, IPIV, W, LDW, INFO )
  22. *
  23. * .. Scalar Arguments ..
  24. * CHARACTER UPLO
  25. * INTEGER INFO, KB, LDA, LDW, N, NB
  26. * ..
  27. * .. Array Arguments ..
  28. * INTEGER IPIV( * )
  29. * COMPLEX*16 A( LDA, * ), W( LDW, * )
  30. * ..
  31. *
  32. *
  33. *> \par Purpose:
  34. * =============
  35. *>
  36. *> \verbatim
  37. *>
  38. *> ZLAHEF computes a partial factorization of a complex Hermitian
  39. *> matrix A using the Bunch-Kaufman diagonal pivoting method. The
  40. *> partial factorization has the form:
  41. *>
  42. *> A = ( I U12 ) ( A11 0 ) ( I 0 ) if UPLO = 'U', or:
  43. *> ( 0 U22 ) ( 0 D ) ( U12**H U22**H )
  44. *>
  45. *> A = ( L11 0 ) ( D 0 ) ( L11**H L21**H ) if UPLO = 'L'
  46. *> ( L21 I ) ( 0 A22 ) ( 0 I )
  47. *>
  48. *> where the order of D is at most NB. The actual order is returned in
  49. *> the argument KB, and is either NB or NB-1, or N if N <= NB.
  50. *> Note that U**H denotes the conjugate transpose of U.
  51. *>
  52. *> ZLAHEF is an auxiliary routine called by ZHETRF. It uses blocked code
  53. *> (calling Level 3 BLAS) to update the submatrix A11 (if UPLO = 'U') or
  54. *> A22 (if UPLO = 'L').
  55. *> \endverbatim
  56. *
  57. * Arguments:
  58. * ==========
  59. *
  60. *> \param[in] UPLO
  61. *> \verbatim
  62. *> UPLO is CHARACTER*1
  63. *> Specifies whether the upper or lower triangular part of the
  64. *> Hermitian matrix A is stored:
  65. *> = 'U': Upper triangular
  66. *> = 'L': Lower triangular
  67. *> \endverbatim
  68. *>
  69. *> \param[in] N
  70. *> \verbatim
  71. *> N is INTEGER
  72. *> The order of the matrix A. N >= 0.
  73. *> \endverbatim
  74. *>
  75. *> \param[in] NB
  76. *> \verbatim
  77. *> NB is INTEGER
  78. *> The maximum number of columns of the matrix A that should be
  79. *> factored. NB should be at least 2 to allow for 2-by-2 pivot
  80. *> blocks.
  81. *> \endverbatim
  82. *>
  83. *> \param[out] KB
  84. *> \verbatim
  85. *> KB is INTEGER
  86. *> The number of columns of A that were actually factored.
  87. *> KB is either NB-1 or NB, or N if N <= NB.
  88. *> \endverbatim
  89. *>
  90. *> \param[in,out] A
  91. *> \verbatim
  92. *> A is COMPLEX*16 array, dimension (LDA,N)
  93. *> On entry, the Hermitian matrix A. If UPLO = 'U', the leading
  94. *> n-by-n upper triangular part of A contains the upper
  95. *> triangular part of the matrix A, and the strictly lower
  96. *> triangular part of A is not referenced. If UPLO = 'L', the
  97. *> leading n-by-n lower triangular part of A contains the lower
  98. *> triangular part of the matrix A, and the strictly upper
  99. *> triangular part of A is not referenced.
  100. *> On exit, A contains details of the partial factorization.
  101. *> \endverbatim
  102. *>
  103. *> \param[in] LDA
  104. *> \verbatim
  105. *> LDA is INTEGER
  106. *> The leading dimension of the array A. LDA >= max(1,N).
  107. *> \endverbatim
  108. *>
  109. *> \param[out] IPIV
  110. *> \verbatim
  111. *> IPIV is INTEGER array, dimension (N)
  112. *> Details of the interchanges and the block structure of D.
  113. *> If UPLO = 'U', only the last KB elements of IPIV are set;
  114. *> if UPLO = 'L', only the first KB elements are set.
  115. *>
  116. *> If IPIV(k) > 0, then rows and columns k and IPIV(k) were
  117. *> interchanged and D(k,k) is a 1-by-1 diagonal block.
  118. *> If UPLO = 'U' and IPIV(k) = IPIV(k-1) < 0, then rows and
  119. *> columns k-1 and -IPIV(k) were interchanged and D(k-1:k,k-1:k)
  120. *> is a 2-by-2 diagonal block. If UPLO = 'L' and IPIV(k) =
  121. *> IPIV(k+1) < 0, then rows and columns k+1 and -IPIV(k) were
  122. *> interchanged and D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
  123. *> \endverbatim
  124. *>
  125. *> \param[out] W
  126. *> \verbatim
  127. *> W is COMPLEX*16 array, dimension (LDW,NB)
  128. *> \endverbatim
  129. *>
  130. *> \param[in] LDW
  131. *> \verbatim
  132. *> LDW is INTEGER
  133. *> The leading dimension of the array W. LDW >= max(1,N).
  134. *> \endverbatim
  135. *>
  136. *> \param[out] INFO
  137. *> \verbatim
  138. *> INFO is INTEGER
  139. *> = 0: successful exit
  140. *> > 0: if INFO = k, D(k,k) is exactly zero. The factorization
  141. *> has been completed, but the block diagonal matrix D is
  142. *> exactly singular.
  143. *> \endverbatim
  144. *
  145. * Authors:
  146. * ========
  147. *
  148. *> \author Univ. of Tennessee
  149. *> \author Univ. of California Berkeley
  150. *> \author Univ. of Colorado Denver
  151. *> \author NAG Ltd.
  152. *
  153. *> \date September 2012
  154. *
  155. *> \ingroup complex16HEcomputational
  156. *
  157. * =====================================================================
  158. SUBROUTINE ZLAHEF( UPLO, N, NB, KB, A, LDA, IPIV, W, LDW, INFO )
  159. *
  160. * -- LAPACK computational routine (version 3.4.2) --
  161. * -- LAPACK is a software package provided by Univ. of Tennessee, --
  162. * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
  163. * September 2012
  164. *
  165. * .. Scalar Arguments ..
  166. CHARACTER UPLO
  167. INTEGER INFO, KB, LDA, LDW, N, NB
  168. * ..
  169. * .. Array Arguments ..
  170. INTEGER IPIV( * )
  171. COMPLEX*16 A( LDA, * ), W( LDW, * )
  172. * ..
  173. *
  174. * =====================================================================
  175. *
  176. * .. Parameters ..
  177. DOUBLE PRECISION ZERO, ONE
  178. PARAMETER ( ZERO = 0.0D+0, ONE = 1.0D+0 )
  179. COMPLEX*16 CONE
  180. PARAMETER ( CONE = ( 1.0D+0, 0.0D+0 ) )
  181. DOUBLE PRECISION EIGHT, SEVTEN
  182. PARAMETER ( EIGHT = 8.0D+0, SEVTEN = 17.0D+0 )
  183. * ..
  184. * .. Local Scalars ..
  185. INTEGER IMAX, J, JB, JJ, JMAX, JP, K, KK, KKW, KP,
  186. $ KSTEP, KW
  187. DOUBLE PRECISION ABSAKK, ALPHA, COLMAX, R1, ROWMAX, T
  188. COMPLEX*16 D11, D21, D22, Z
  189. * ..
  190. * .. External Functions ..
  191. LOGICAL LSAME
  192. INTEGER IZAMAX
  193. EXTERNAL LSAME, IZAMAX
  194. * ..
  195. * .. External Subroutines ..
  196. EXTERNAL ZCOPY, ZDSCAL, ZGEMM, ZGEMV, ZLACGV, ZSWAP
  197. * ..
  198. * .. Intrinsic Functions ..
  199. INTRINSIC ABS, DBLE, DCONJG, DIMAG, MAX, MIN, SQRT
  200. * ..
  201. * .. Statement Functions ..
  202. DOUBLE PRECISION CABS1
  203. * ..
  204. * .. Statement Function definitions ..
  205. CABS1( Z ) = ABS( DBLE( Z ) ) + ABS( DIMAG( Z ) )
  206. * ..
  207. * .. Executable Statements ..
  208. *
  209. INFO = 0
  210. *
  211. * Initialize ALPHA for use in choosing pivot block size.
  212. *
  213. ALPHA = ( ONE+SQRT( SEVTEN ) ) / EIGHT
  214. *
  215. IF( LSAME( UPLO, 'U' ) ) THEN
  216. *
  217. * Factorize the trailing columns of A using the upper triangle
  218. * of A and working backwards, and compute the matrix W = U12*D
  219. * for use in updating A11 (note that conjg(W) is actually stored)
  220. *
  221. * K is the main loop index, decreasing from N in steps of 1 or 2
  222. *
  223. * KW is the column of W which corresponds to column K of A
  224. *
  225. K = N
  226. 10 CONTINUE
  227. KW = NB + K - N
  228. *
  229. * Exit from loop
  230. *
  231. IF( ( K.LE.N-NB+1 .AND. NB.LT.N ) .OR. K.LT.1 )
  232. $ GO TO 30
  233. *
  234. * Copy column K of A to column KW of W and update it
  235. *
  236. CALL ZCOPY( K-1, A( 1, K ), 1, W( 1, KW ), 1 )
  237. W( K, KW ) = DBLE( A( K, K ) )
  238. IF( K.LT.N ) THEN
  239. CALL ZGEMV( 'No transpose', K, N-K, -CONE, A( 1, K+1 ), LDA,
  240. $ W( K, KW+1 ), LDW, CONE, W( 1, KW ), 1 )
  241. W( K, KW ) = DBLE( W( K, KW ) )
  242. END IF
  243. *
  244. KSTEP = 1
  245. *
  246. * Determine rows and columns to be interchanged and whether
  247. * a 1-by-1 or 2-by-2 pivot block will be used
  248. *
  249. ABSAKK = ABS( DBLE( W( K, KW ) ) )
  250. *
  251. * IMAX is the row-index of the largest off-diagonal element in
  252. * column K, and COLMAX is its absolute value
  253. *
  254. IF( K.GT.1 ) THEN
  255. IMAX = IZAMAX( K-1, W( 1, KW ), 1 )
  256. COLMAX = CABS1( W( IMAX, KW ) )
  257. ELSE
  258. COLMAX = ZERO
  259. END IF
  260. *
  261. IF( MAX( ABSAKK, COLMAX ).EQ.ZERO ) THEN
  262. *
  263. * Column K is zero: set INFO and continue
  264. *
  265. IF( INFO.EQ.0 )
  266. $ INFO = K
  267. KP = K
  268. A( K, K ) = DBLE( A( K, K ) )
  269. ELSE
  270. IF( ABSAKK.GE.ALPHA*COLMAX ) THEN
  271. *
  272. * no interchange, use 1-by-1 pivot block
  273. *
  274. KP = K
  275. ELSE
  276. *
  277. * Copy column IMAX to column KW-1 of W and update it
  278. *
  279. CALL ZCOPY( IMAX-1, A( 1, IMAX ), 1, W( 1, KW-1 ), 1 )
  280. W( IMAX, KW-1 ) = DBLE( A( IMAX, IMAX ) )
  281. CALL ZCOPY( K-IMAX, A( IMAX, IMAX+1 ), LDA,
  282. $ W( IMAX+1, KW-1 ), 1 )
  283. CALL ZLACGV( K-IMAX, W( IMAX+1, KW-1 ), 1 )
  284. IF( K.LT.N ) THEN
  285. CALL ZGEMV( 'No transpose', K, N-K, -CONE,
  286. $ A( 1, K+1 ), LDA, W( IMAX, KW+1 ), LDW,
  287. $ CONE, W( 1, KW-1 ), 1 )
  288. W( IMAX, KW-1 ) = DBLE( W( IMAX, KW-1 ) )
  289. END IF
  290. *
  291. * JMAX is the column-index of the largest off-diagonal
  292. * element in row IMAX, and ROWMAX is its absolute value
  293. *
  294. JMAX = IMAX + IZAMAX( K-IMAX, W( IMAX+1, KW-1 ), 1 )
  295. ROWMAX = CABS1( W( JMAX, KW-1 ) )
  296. IF( IMAX.GT.1 ) THEN
  297. JMAX = IZAMAX( IMAX-1, W( 1, KW-1 ), 1 )
  298. ROWMAX = MAX( ROWMAX, CABS1( W( JMAX, KW-1 ) ) )
  299. END IF
  300. *
  301. IF( ABSAKK.GE.ALPHA*COLMAX*( COLMAX / ROWMAX ) ) THEN
  302. *
  303. * no interchange, use 1-by-1 pivot block
  304. *
  305. KP = K
  306. ELSE IF( ABS( DBLE( W( IMAX, KW-1 ) ) ).GE.ALPHA*ROWMAX )
  307. $ THEN
  308. *
  309. * interchange rows and columns K and IMAX, use 1-by-1
  310. * pivot block
  311. *
  312. KP = IMAX
  313. *
  314. * copy column KW-1 of W to column KW
  315. *
  316. CALL ZCOPY( K, W( 1, KW-1 ), 1, W( 1, KW ), 1 )
  317. ELSE
  318. *
  319. * interchange rows and columns K-1 and IMAX, use 2-by-2
  320. * pivot block
  321. *
  322. KP = IMAX
  323. KSTEP = 2
  324. END IF
  325. END IF
  326. *
  327. KK = K - KSTEP + 1
  328. KKW = NB + KK - N
  329. *
  330. * Updated column KP is already stored in column KKW of W
  331. *
  332. IF( KP.NE.KK ) THEN
  333. *
  334. * Copy non-updated column KK to column KP
  335. *
  336. A( KP, KP ) = DBLE( A( KK, KK ) )
  337. CALL ZCOPY( KK-1-KP, A( KP+1, KK ), 1, A( KP, KP+1 ),
  338. $ LDA )
  339. CALL ZLACGV( KK-1-KP, A( KP, KP+1 ), LDA )
  340. CALL ZCOPY( KP-1, A( 1, KK ), 1, A( 1, KP ), 1 )
  341. *
  342. * Interchange rows KK and KP in last KK columns of A and W
  343. *
  344. IF( KK.LT.N )
  345. $ CALL ZSWAP( N-KK, A( KK, KK+1 ), LDA, A( KP, KK+1 ),
  346. $ LDA )
  347. CALL ZSWAP( N-KK+1, W( KK, KKW ), LDW, W( KP, KKW ),
  348. $ LDW )
  349. END IF
  350. *
  351. IF( KSTEP.EQ.1 ) THEN
  352. *
  353. * 1-by-1 pivot block D(k): column KW of W now holds
  354. *
  355. * W(k) = U(k)*D(k)
  356. *
  357. * where U(k) is the k-th column of U
  358. *
  359. * Store U(k) in column k of A
  360. *
  361. CALL ZCOPY( K, W( 1, KW ), 1, A( 1, K ), 1 )
  362. R1 = ONE / DBLE( A( K, K ) )
  363. CALL ZDSCAL( K-1, R1, A( 1, K ), 1 )
  364. *
  365. * Conjugate W(k)
  366. *
  367. CALL ZLACGV( K-1, W( 1, KW ), 1 )
  368. ELSE
  369. *
  370. * 2-by-2 pivot block D(k): columns KW and KW-1 of W now
  371. * hold
  372. *
  373. * ( W(k-1) W(k) ) = ( U(k-1) U(k) )*D(k)
  374. *
  375. * where U(k) and U(k-1) are the k-th and (k-1)-th columns
  376. * of U
  377. *
  378. IF( K.GT.2 ) THEN
  379. *
  380. * Store U(k) and U(k-1) in columns k and k-1 of A
  381. *
  382. D21 = W( K-1, KW )
  383. D11 = W( K, KW ) / DCONJG( D21 )
  384. D22 = W( K-1, KW-1 ) / D21
  385. T = ONE / ( DBLE( D11*D22 )-ONE )
  386. D21 = T / D21
  387. DO 20 J = 1, K - 2
  388. A( J, K-1 ) = D21*( D11*W( J, KW-1 )-W( J, KW ) )
  389. A( J, K ) = DCONJG( D21 )*
  390. $ ( D22*W( J, KW )-W( J, KW-1 ) )
  391. 20 CONTINUE
  392. END IF
  393. *
  394. * Copy D(k) to A
  395. *
  396. A( K-1, K-1 ) = W( K-1, KW-1 )
  397. A( K-1, K ) = W( K-1, KW )
  398. A( K, K ) = W( K, KW )
  399. *
  400. * Conjugate W(k) and W(k-1)
  401. *
  402. CALL ZLACGV( K-1, W( 1, KW ), 1 )
  403. CALL ZLACGV( K-2, W( 1, KW-1 ), 1 )
  404. END IF
  405. END IF
  406. *
  407. * Store details of the interchanges in IPIV
  408. *
  409. IF( KSTEP.EQ.1 ) THEN
  410. IPIV( K ) = KP
  411. ELSE
  412. IPIV( K ) = -KP
  413. IPIV( K-1 ) = -KP
  414. END IF
  415. *
  416. * Decrease K and return to the start of the main loop
  417. *
  418. K = K - KSTEP
  419. GO TO 10
  420. *
  421. 30 CONTINUE
  422. *
  423. * Update the upper triangle of A11 (= A(1:k,1:k)) as
  424. *
  425. * A11 := A11 - U12*D*U12**H = A11 - U12*W**H
  426. *
  427. * computing blocks of NB columns at a time (note that conjg(W) is
  428. * actually stored)
  429. *
  430. DO 50 J = ( ( K-1 ) / NB )*NB + 1, 1, -NB
  431. JB = MIN( NB, K-J+1 )
  432. *
  433. * Update the upper triangle of the diagonal block
  434. *
  435. DO 40 JJ = J, J + JB - 1
  436. A( JJ, JJ ) = DBLE( A( JJ, JJ ) )
  437. CALL ZGEMV( 'No transpose', JJ-J+1, N-K, -CONE,
  438. $ A( J, K+1 ), LDA, W( JJ, KW+1 ), LDW, CONE,
  439. $ A( J, JJ ), 1 )
  440. A( JJ, JJ ) = DBLE( A( JJ, JJ ) )
  441. 40 CONTINUE
  442. *
  443. * Update the rectangular superdiagonal block
  444. *
  445. CALL ZGEMM( 'No transpose', 'Transpose', J-1, JB, N-K,
  446. $ -CONE, A( 1, K+1 ), LDA, W( J, KW+1 ), LDW,
  447. $ CONE, A( 1, J ), LDA )
  448. 50 CONTINUE
  449. *
  450. * Put U12 in standard form by partially undoing the interchanges
  451. * in columns k+1:n
  452. *
  453. J = K + 1
  454. 60 CONTINUE
  455. JJ = J
  456. JP = IPIV( J )
  457. IF( JP.LT.0 ) THEN
  458. JP = -JP
  459. J = J + 1
  460. END IF
  461. J = J + 1
  462. IF( JP.NE.JJ .AND. J.LE.N )
  463. $ CALL ZSWAP( N-J+1, A( JP, J ), LDA, A( JJ, J ), LDA )
  464. IF( J.LE.N )
  465. $ GO TO 60
  466. *
  467. * Set KB to the number of columns factorized
  468. *
  469. KB = N - K
  470. *
  471. ELSE
  472. *
  473. * Factorize the leading columns of A using the lower triangle
  474. * of A and working forwards, and compute the matrix W = L21*D
  475. * for use in updating A22 (note that conjg(W) is actually stored)
  476. *
  477. * K is the main loop index, increasing from 1 in steps of 1 or 2
  478. *
  479. K = 1
  480. 70 CONTINUE
  481. *
  482. * Exit from loop
  483. *
  484. IF( ( K.GE.NB .AND. NB.LT.N ) .OR. K.GT.N )
  485. $ GO TO 90
  486. *
  487. * Copy column K of A to column K of W and update it
  488. *
  489. W( K, K ) = DBLE( A( K, K ) )
  490. IF( K.LT.N )
  491. $ CALL ZCOPY( N-K, A( K+1, K ), 1, W( K+1, K ), 1 )
  492. CALL ZGEMV( 'No transpose', N-K+1, K-1, -CONE, A( K, 1 ), LDA,
  493. $ W( K, 1 ), LDW, CONE, W( K, K ), 1 )
  494. W( K, K ) = DBLE( W( K, K ) )
  495. *
  496. KSTEP = 1
  497. *
  498. * Determine rows and columns to be interchanged and whether
  499. * a 1-by-1 or 2-by-2 pivot block will be used
  500. *
  501. ABSAKK = ABS( DBLE( W( K, K ) ) )
  502. *
  503. * IMAX is the row-index of the largest off-diagonal element in
  504. * column K, and COLMAX is its absolute value
  505. *
  506. IF( K.LT.N ) THEN
  507. IMAX = K + IZAMAX( N-K, W( K+1, K ), 1 )
  508. COLMAX = CABS1( W( IMAX, K ) )
  509. ELSE
  510. COLMAX = ZERO
  511. END IF
  512. *
  513. IF( MAX( ABSAKK, COLMAX ).EQ.ZERO ) THEN
  514. *
  515. * Column K is zero: set INFO and continue
  516. *
  517. IF( INFO.EQ.0 )
  518. $ INFO = K
  519. KP = K
  520. A( K, K ) = DBLE( A( K, K ) )
  521. ELSE
  522. IF( ABSAKK.GE.ALPHA*COLMAX ) THEN
  523. *
  524. * no interchange, use 1-by-1 pivot block
  525. *
  526. KP = K
  527. ELSE
  528. *
  529. * Copy column IMAX to column K+1 of W and update it
  530. *
  531. CALL ZCOPY( IMAX-K, A( IMAX, K ), LDA, W( K, K+1 ), 1 )
  532. CALL ZLACGV( IMAX-K, W( K, K+1 ), 1 )
  533. W( IMAX, K+1 ) = DBLE( A( IMAX, IMAX ) )
  534. IF( IMAX.LT.N )
  535. $ CALL ZCOPY( N-IMAX, A( IMAX+1, IMAX ), 1,
  536. $ W( IMAX+1, K+1 ), 1 )
  537. CALL ZGEMV( 'No transpose', N-K+1, K-1, -CONE, A( K, 1 ),
  538. $ LDA, W( IMAX, 1 ), LDW, CONE, W( K, K+1 ),
  539. $ 1 )
  540. W( IMAX, K+1 ) = DBLE( W( IMAX, K+1 ) )
  541. *
  542. * JMAX is the column-index of the largest off-diagonal
  543. * element in row IMAX, and ROWMAX is its absolute value
  544. *
  545. JMAX = K - 1 + IZAMAX( IMAX-K, W( K, K+1 ), 1 )
  546. ROWMAX = CABS1( W( JMAX, K+1 ) )
  547. IF( IMAX.LT.N ) THEN
  548. JMAX = IMAX + IZAMAX( N-IMAX, W( IMAX+1, K+1 ), 1 )
  549. ROWMAX = MAX( ROWMAX, CABS1( W( JMAX, K+1 ) ) )
  550. END IF
  551. *
  552. IF( ABSAKK.GE.ALPHA*COLMAX*( COLMAX / ROWMAX ) ) THEN
  553. *
  554. * no interchange, use 1-by-1 pivot block
  555. *
  556. KP = K
  557. ELSE IF( ABS( DBLE( W( IMAX, K+1 ) ) ).GE.ALPHA*ROWMAX )
  558. $ THEN
  559. *
  560. * interchange rows and columns K and IMAX, use 1-by-1
  561. * pivot block
  562. *
  563. KP = IMAX
  564. *
  565. * copy column K+1 of W to column K
  566. *
  567. CALL ZCOPY( N-K+1, W( K, K+1 ), 1, W( K, K ), 1 )
  568. ELSE
  569. *
  570. * interchange rows and columns K+1 and IMAX, use 2-by-2
  571. * pivot block
  572. *
  573. KP = IMAX
  574. KSTEP = 2
  575. END IF
  576. END IF
  577. *
  578. KK = K + KSTEP - 1
  579. *
  580. * Updated column KP is already stored in column KK of W
  581. *
  582. IF( KP.NE.KK ) THEN
  583. *
  584. * Copy non-updated column KK to column KP
  585. *
  586. A( KP, KP ) = DBLE( A( KK, KK ) )
  587. CALL ZCOPY( KP-KK-1, A( KK+1, KK ), 1, A( KP, KK+1 ),
  588. $ LDA )
  589. CALL ZLACGV( KP-KK-1, A( KP, KK+1 ), LDA )
  590. IF( KP.LT.N )
  591. $ CALL ZCOPY( N-KP, A( KP+1, KK ), 1, A( KP+1, KP ), 1 )
  592. *
  593. * Interchange rows KK and KP in first KK columns of A and W
  594. *
  595. CALL ZSWAP( KK-1, A( KK, 1 ), LDA, A( KP, 1 ), LDA )
  596. CALL ZSWAP( KK, W( KK, 1 ), LDW, W( KP, 1 ), LDW )
  597. END IF
  598. *
  599. IF( KSTEP.EQ.1 ) THEN
  600. *
  601. * 1-by-1 pivot block D(k): column k of W now holds
  602. *
  603. * W(k) = L(k)*D(k)
  604. *
  605. * where L(k) is the k-th column of L
  606. *
  607. * Store L(k) in column k of A
  608. *
  609. CALL ZCOPY( N-K+1, W( K, K ), 1, A( K, K ), 1 )
  610. IF( K.LT.N ) THEN
  611. R1 = ONE / DBLE( A( K, K ) )
  612. CALL ZDSCAL( N-K, R1, A( K+1, K ), 1 )
  613. *
  614. * Conjugate W(k)
  615. *
  616. CALL ZLACGV( N-K, W( K+1, K ), 1 )
  617. END IF
  618. ELSE
  619. *
  620. * 2-by-2 pivot block D(k): columns k and k+1 of W now hold
  621. *
  622. * ( W(k) W(k+1) ) = ( L(k) L(k+1) )*D(k)
  623. *
  624. * where L(k) and L(k+1) are the k-th and (k+1)-th columns
  625. * of L
  626. *
  627. IF( K.LT.N-1 ) THEN
  628. *
  629. * Store L(k) and L(k+1) in columns k and k+1 of A
  630. *
  631. D21 = W( K+1, K )
  632. D11 = W( K+1, K+1 ) / D21
  633. D22 = W( K, K ) / DCONJG( D21 )
  634. T = ONE / ( DBLE( D11*D22 )-ONE )
  635. D21 = T / D21
  636. DO 80 J = K + 2, N
  637. A( J, K ) = DCONJG( D21 )*
  638. $ ( D11*W( J, K )-W( J, K+1 ) )
  639. A( J, K+1 ) = D21*( D22*W( J, K+1 )-W( J, K ) )
  640. 80 CONTINUE
  641. END IF
  642. *
  643. * Copy D(k) to A
  644. *
  645. A( K, K ) = W( K, K )
  646. A( K+1, K ) = W( K+1, K )
  647. A( K+1, K+1 ) = W( K+1, K+1 )
  648. *
  649. * Conjugate W(k) and W(k+1)
  650. *
  651. CALL ZLACGV( N-K, W( K+1, K ), 1 )
  652. CALL ZLACGV( N-K-1, W( K+2, K+1 ), 1 )
  653. END IF
  654. END IF
  655. *
  656. * Store details of the interchanges in IPIV
  657. *
  658. IF( KSTEP.EQ.1 ) THEN
  659. IPIV( K ) = KP
  660. ELSE
  661. IPIV( K ) = -KP
  662. IPIV( K+1 ) = -KP
  663. END IF
  664. *
  665. * Increase K and return to the start of the main loop
  666. *
  667. K = K + KSTEP
  668. GO TO 70
  669. *
  670. 90 CONTINUE
  671. *
  672. * Update the lower triangle of A22 (= A(k:n,k:n)) as
  673. *
  674. * A22 := A22 - L21*D*L21**H = A22 - L21*W**H
  675. *
  676. * computing blocks of NB columns at a time (note that conjg(W) is
  677. * actually stored)
  678. *
  679. DO 110 J = K, N, NB
  680. JB = MIN( NB, N-J+1 )
  681. *
  682. * Update the lower triangle of the diagonal block
  683. *
  684. DO 100 JJ = J, J + JB - 1
  685. A( JJ, JJ ) = DBLE( A( JJ, JJ ) )
  686. CALL ZGEMV( 'No transpose', J+JB-JJ, K-1, -CONE,
  687. $ A( JJ, 1 ), LDA, W( JJ, 1 ), LDW, CONE,
  688. $ A( JJ, JJ ), 1 )
  689. A( JJ, JJ ) = DBLE( A( JJ, JJ ) )
  690. 100 CONTINUE
  691. *
  692. * Update the rectangular subdiagonal block
  693. *
  694. IF( J+JB.LE.N )
  695. $ CALL ZGEMM( 'No transpose', 'Transpose', N-J-JB+1, JB,
  696. $ K-1, -CONE, A( J+JB, 1 ), LDA, W( J, 1 ),
  697. $ LDW, CONE, A( J+JB, J ), LDA )
  698. 110 CONTINUE
  699. *
  700. * Put L21 in standard form by partially undoing the interchanges
  701. * in columns 1:k-1
  702. *
  703. J = K - 1
  704. 120 CONTINUE
  705. JJ = J
  706. JP = IPIV( J )
  707. IF( JP.LT.0 ) THEN
  708. JP = -JP
  709. J = J - 1
  710. END IF
  711. J = J - 1
  712. IF( JP.NE.JJ .AND. J.GE.1 )
  713. $ CALL ZSWAP( J, A( JP, 1 ), LDA, A( JJ, 1 ), LDA )
  714. IF( J.GE.1 )
  715. $ GO TO 120
  716. *
  717. * Set KB to the number of columns factorized
  718. *
  719. KB = K - 1
  720. *
  721. END IF
  722. RETURN
  723. *
  724. * End of ZLAHEF
  725. *
  726. END