LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
clahef.f
Go to the documentation of this file.
1 *> \brief \b CLAHEF 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 CLAHEF + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/clahef.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/clahef.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/clahef.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE CLAHEF( 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 A( LDA, * ), W( LDW, * )
30 * ..
31 *
32 *
33 *> \par Purpose:
34 * =============
35 *>
36 *> \verbatim
37 *>
38 *> CLAHEF 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 *> CLAHEF is an auxiliary routine called by CHETRF. 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 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 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 complexHEcomputational
156 *
157 * =====================================================================
158  SUBROUTINE clahef( 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 a( lda, * ), w( ldw, * )
172 * ..
173 *
174 * =====================================================================
175 *
176 * .. Parameters ..
177  REAL zero, one
178  parameter( zero = 0.0e+0, one = 1.0e+0 )
179  COMPLEX cone
180  parameter( cone = ( 1.0e+0, 0.0e+0 ) )
181  REAL eight, sevten
182  parameter( eight = 8.0e+0, sevten = 17.0e+0 )
183 * ..
184 * .. Local Scalars ..
185  INTEGER imax, j, jb, jj, jmax, jp, k, kk, kkw, kp,
186  $ kstep, kw
187  REAL absakk, alpha, colmax, r1, rowmax, t
188  COMPLEX d11, d21, d22, z
189 * ..
190 * .. External Functions ..
191  LOGICAL lsame
192  INTEGER icamax
193  EXTERNAL lsame, icamax
194 * ..
195 * .. External Subroutines ..
196  EXTERNAL ccopy, cgemm, cgemv, clacgv, csscal, cswap
197 * ..
198 * .. Intrinsic Functions ..
199  INTRINSIC abs, aimag, conjg, max, min, REAL, sqrt
200 * ..
201 * .. Statement Functions ..
202  REAL cabs1
203 * ..
204 * .. Statement Function definitions ..
205  cabs1( z ) = abs( REAL( Z ) ) + abs( aimag( 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 ccopy( k-1, a( 1, k ), 1, w( 1, kw ), 1 )
237  w( k, kw ) = REAL( A( K, K ) )
238  IF( k.LT.n ) THEN
239  CALL cgemv( '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 ) = REAL( 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( REAL( 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 = icamax( 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 ) = REAL( 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 ccopy( imax-1, a( 1, imax ), 1, w( 1, kw-1 ), 1 )
280  w( imax, kw-1 ) = REAL( A( IMAX, IMAX ) )
281  CALL ccopy( k-imax, a( imax, imax+1 ), lda,
282  $ w( imax+1, kw-1 ), 1 )
283  CALL clacgv( k-imax, w( imax+1, kw-1 ), 1 )
284  IF( k.LT.n ) THEN
285  CALL cgemv( '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 ) = REAL( 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 + icamax( k-imax, w( imax+1, kw-1 ), 1 )
295  rowmax = cabs1( w( jmax, kw-1 ) )
296  IF( imax.GT.1 ) THEN
297  jmax = icamax( 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( REAL( 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 ccopy( 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 ) = REAL( A( KK, KK ) )
337  CALL ccopy( kk-1-kp, a( kp+1, kk ), 1, a( kp, kp+1 ),
338  $ lda )
339  CALL clacgv( kk-1-kp, a( kp, kp+1 ), lda )
340  CALL ccopy( 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 cswap( n-kk, a( kk, kk+1 ), lda, a( kp, kk+1 ),
346  $ lda )
347  CALL cswap( 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 ccopy( k, w( 1, kw ), 1, a( 1, k ), 1 )
362  r1 = one / REAL( A( K, K ) )
363  CALL csscal( k-1, r1, a( 1, k ), 1 )
364 *
365 * Conjugate W(k)
366 *
367  CALL clacgv( 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 ) / conjg( d21 )
384  d22 = w( k-1, kw-1 ) / d21
385  t = one / ( REAL( 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 ) = conjg( 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 clacgv( k-1, w( 1, kw ), 1 )
403  CALL clacgv( 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 ) = REAL( A( JJ, JJ ) )
437  CALL cgemv( '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 ) = REAL( A( JJ, JJ ) )
441  40 continue
442 *
443 * Update the rectangular superdiagonal block
444 *
445  CALL cgemm( '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 cswap( 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 ) = REAL( A( K, K ) )
490  IF( k.LT.n )
491  $ CALL ccopy( n-k, a( k+1, k ), 1, w( k+1, k ), 1 )
492  CALL cgemv( '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 ) = REAL( 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( REAL( 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 + icamax( 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 ) = REAL( 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 ccopy( imax-k, a( imax, k ), lda, w( k, k+1 ), 1 )
532  CALL clacgv( imax-k, w( k, k+1 ), 1 )
533  w( imax, k+1 ) = REAL( A( IMAX, IMAX ) )
534  IF( imax.LT.n )
535  $ CALL ccopy( n-imax, a( imax+1, imax ), 1,
536  $ w( imax+1, k+1 ), 1 )
537  CALL cgemv( '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 ) = REAL( 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 + icamax( imax-k, w( k, k+1 ), 1 )
546  rowmax = cabs1( w( jmax, k+1 ) )
547  IF( imax.LT.n ) THEN
548  jmax = imax + icamax( 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( REAL( 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 ccopy( 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 ) = REAL( A( KK, KK ) )
587  CALL ccopy( kp-kk-1, a( kk+1, kk ), 1, a( kp, kk+1 ),
588  $ lda )
589  CALL clacgv( kp-kk-1, a( kp, kk+1 ), lda )
590  IF( kp.LT.n )
591  $ CALL ccopy( 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 cswap( kk-1, a( kk, 1 ), lda, a( kp, 1 ), lda )
596  CALL cswap( 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 ccopy( n-k+1, w( k, k ), 1, a( k, k ), 1 )
610  IF( k.LT.n ) THEN
611  r1 = one / REAL( A( K, K ) )
612  CALL csscal( n-k, r1, a( k+1, k ), 1 )
613 *
614 * Conjugate W(k)
615 *
616  CALL clacgv( 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 ) / conjg( d21 )
634  t = one / ( REAL( d11*d22 )-one )
635  d21 = t / d21
636  DO 80 j = k + 2, n
637  a( j, k ) = conjg( 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 clacgv( n-k, w( k+1, k ), 1 )
652  CALL clacgv( 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 ) = REAL( A( JJ, JJ ) )
686  CALL cgemv( '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 ) = REAL( A( JJ, JJ ) )
690  100 continue
691 *
692 * Update the rectangular subdiagonal block
693 *
694  IF( j+jb.LE.n )
695  $ CALL cgemm( '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 cswap( 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 CLAHEF
725 *
726  END