LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zlasyf.f
Go to the documentation of this file.
1 *> \brief \b ZLASYF computes a partial factorization of a complex symmetric 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 ZLASYF + dependencies
10 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zlasyf.f">
11 *> [TGZ]</a>
12 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zlasyf.f">
13 *> [ZIP]</a>
14 *> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zlasyf.f">
15 *> [TXT]</a>
16 *> \endhtmlonly
17 *
18 * Definition:
19 * ===========
20 *
21 * SUBROUTINE ZLASYF( 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 *> ZLASYF computes a partial factorization of a complex symmetric matrix
39 *> A using the Bunch-Kaufman diagonal pivoting method. The partial
40 *> factorization has the form:
41 *>
42 *> A = ( I U12 ) ( A11 0 ) ( I 0 ) if UPLO = 'U', or:
43 *> ( 0 U22 ) ( 0 D ) ( U12**T U22**T )
44 *>
45 *> A = ( L11 0 ) ( D 0 ) ( L11**T L21**T ) 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**T denotes the transpose of U.
51 *>
52 *> ZLASYF is an auxiliary routine called by ZSYTRF. 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 *> symmetric 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 symmetric 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 complex16SYcomputational
156 *
157 * =====================================================================
158  SUBROUTINE zlasyf( 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  DOUBLE PRECISION eight, sevten
180  parameter( eight = 8.0d+0, sevten = 17.0d+0 )
181  COMPLEX*16 cone
182  parameter( cone = ( 1.0d+0, 0.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, rowmax
188  COMPLEX*16 d11, d21, d22, r1, t, z
189 * ..
190 * .. External Functions ..
191  LOGICAL lsame
192  INTEGER izamax
193  EXTERNAL lsame, izamax
194 * ..
195 * .. External Subroutines ..
196  EXTERNAL zcopy, zgemm, zgemv, zscal, zswap
197 * ..
198 * .. Intrinsic Functions ..
199  INTRINSIC abs, dble, 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
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, a( 1, k ), 1, w( 1, kw ), 1 )
237  IF( k.LT.n )
238  $ CALL zgemv( 'No transpose', k, n-k, -cone, a( 1, k+1 ), lda,
239  $ w( k, kw+1 ), ldw, cone, w( 1, kw ), 1 )
240 *
241  kstep = 1
242 *
243 * Determine rows and columns to be interchanged and whether
244 * a 1-by-1 or 2-by-2 pivot block will be used
245 *
246  absakk = cabs1( w( k, kw ) )
247 *
248 * IMAX is the row-index of the largest off-diagonal element in
249 * column K, and COLMAX is its absolute value
250 *
251  IF( k.GT.1 ) THEN
252  imax = izamax( k-1, w( 1, kw ), 1 )
253  colmax = cabs1( w( imax, kw ) )
254  ELSE
255  colmax = zero
256  END IF
257 *
258  IF( max( absakk, colmax ).EQ.zero ) THEN
259 *
260 * Column K is zero: set INFO and continue
261 *
262  IF( info.EQ.0 )
263  $ info = k
264  kp = k
265  ELSE
266  IF( absakk.GE.alpha*colmax ) THEN
267 *
268 * no interchange, use 1-by-1 pivot block
269 *
270  kp = k
271  ELSE
272 *
273 * Copy column IMAX to column KW-1 of W and update it
274 *
275  CALL zcopy( imax, a( 1, imax ), 1, w( 1, kw-1 ), 1 )
276  CALL zcopy( k-imax, a( imax, imax+1 ), lda,
277  $ w( imax+1, kw-1 ), 1 )
278  IF( k.LT.n )
279  $ CALL zgemv( 'No transpose', k, n-k, -cone,
280  $ a( 1, k+1 ), lda, w( imax, kw+1 ), ldw,
281  $ cone, w( 1, kw-1 ), 1 )
282 *
283 * JMAX is the column-index of the largest off-diagonal
284 * element in row IMAX, and ROWMAX is its absolute value
285 *
286  jmax = imax + izamax( k-imax, w( imax+1, kw-1 ), 1 )
287  rowmax = cabs1( w( jmax, kw-1 ) )
288  IF( imax.GT.1 ) THEN
289  jmax = izamax( imax-1, w( 1, kw-1 ), 1 )
290  rowmax = max( rowmax, cabs1( w( jmax, kw-1 ) ) )
291  END IF
292 *
293  IF( absakk.GE.alpha*colmax*( colmax / rowmax ) ) THEN
294 *
295 * no interchange, use 1-by-1 pivot block
296 *
297  kp = k
298  ELSE IF( cabs1( w( imax, kw-1 ) ).GE.alpha*rowmax ) THEN
299 *
300 * interchange rows and columns K and IMAX, use 1-by-1
301 * pivot block
302 *
303  kp = imax
304 *
305 * copy column KW-1 of W to column KW
306 *
307  CALL zcopy( k, w( 1, kw-1 ), 1, w( 1, kw ), 1 )
308  ELSE
309 *
310 * interchange rows and columns K-1 and IMAX, use 2-by-2
311 * pivot block
312 *
313  kp = imax
314  kstep = 2
315  END IF
316  END IF
317 *
318  kk = k - kstep + 1
319  kkw = nb + kk - n
320 *
321 * Updated column KP is already stored in column KKW of W
322 *
323  IF( kp.NE.kk ) THEN
324 *
325 * Copy non-updated column KK to column KP
326 *
327  a( kp, k ) = a( kk, k )
328  CALL zcopy( k-1-kp, a( kp+1, kk ), 1, a( kp, kp+1 ),
329  $ lda )
330  CALL zcopy( kp, a( 1, kk ), 1, a( 1, kp ), 1 )
331 *
332 * Interchange rows KK and KP in last KK columns of A and W
333 *
334  CALL zswap( n-kk+1, a( kk, kk ), lda, a( kp, kk ), lda )
335  CALL zswap( n-kk+1, w( kk, kkw ), ldw, w( kp, kkw ),
336  $ ldw )
337  END IF
338 *
339  IF( kstep.EQ.1 ) THEN
340 *
341 * 1-by-1 pivot block D(k): column KW of W now holds
342 *
343 * W(k) = U(k)*D(k)
344 *
345 * where U(k) is the k-th column of U
346 *
347 * Store U(k) in column k of A
348 *
349  CALL zcopy( k, w( 1, kw ), 1, a( 1, k ), 1 )
350  r1 = cone / a( k, k )
351  CALL zscal( k-1, r1, a( 1, k ), 1 )
352  ELSE
353 *
354 * 2-by-2 pivot block D(k): columns KW and KW-1 of W now
355 * hold
356 *
357 * ( W(k-1) W(k) ) = ( U(k-1) U(k) )*D(k)
358 *
359 * where U(k) and U(k-1) are the k-th and (k-1)-th columns
360 * of U
361 *
362  IF( k.GT.2 ) THEN
363 *
364 * Store U(k) and U(k-1) in columns k and k-1 of A
365 *
366  d21 = w( k-1, kw )
367  d11 = w( k, kw ) / d21
368  d22 = w( k-1, kw-1 ) / d21
369  t = cone / ( d11*d22-cone )
370  d21 = t / d21
371  DO 20 j = 1, k - 2
372  a( j, k-1 ) = d21*( d11*w( j, kw-1 )-w( j, kw ) )
373  a( j, k ) = d21*( d22*w( j, kw )-w( j, kw-1 ) )
374  20 continue
375  END IF
376 *
377 * Copy D(k) to A
378 *
379  a( k-1, k-1 ) = w( k-1, kw-1 )
380  a( k-1, k ) = w( k-1, kw )
381  a( k, k ) = w( k, kw )
382  END IF
383  END IF
384 *
385 * Store details of the interchanges in IPIV
386 *
387  IF( kstep.EQ.1 ) THEN
388  ipiv( k ) = kp
389  ELSE
390  ipiv( k ) = -kp
391  ipiv( k-1 ) = -kp
392  END IF
393 *
394 * Decrease K and return to the start of the main loop
395 *
396  k = k - kstep
397  go to 10
398 *
399  30 continue
400 *
401 * Update the upper triangle of A11 (= A(1:k,1:k)) as
402 *
403 * A11 := A11 - U12*D*U12**T = A11 - U12*W**T
404 *
405 * computing blocks of NB columns at a time
406 *
407  DO 50 j = ( ( k-1 ) / nb )*nb + 1, 1, -nb
408  jb = min( nb, k-j+1 )
409 *
410 * Update the upper triangle of the diagonal block
411 *
412  DO 40 jj = j, j + jb - 1
413  CALL zgemv( 'No transpose', jj-j+1, n-k, -cone,
414  $ a( j, k+1 ), lda, w( jj, kw+1 ), ldw, cone,
415  $ a( j, jj ), 1 )
416  40 continue
417 *
418 * Update the rectangular superdiagonal block
419 *
420  CALL zgemm( 'No transpose', 'Transpose', j-1, jb, n-k,
421  $ -cone, a( 1, k+1 ), lda, w( j, kw+1 ), ldw,
422  $ cone, a( 1, j ), lda )
423  50 continue
424 *
425 * Put U12 in standard form by partially undoing the interchanges
426 * in columns k+1:n
427 *
428  j = k + 1
429  60 continue
430  jj = j
431  jp = ipiv( j )
432  IF( jp.LT.0 ) THEN
433  jp = -jp
434  j = j + 1
435  END IF
436  j = j + 1
437  IF( jp.NE.jj .AND. j.LE.n )
438  $ CALL zswap( n-j+1, a( jp, j ), lda, a( jj, j ), lda )
439  IF( j.LE.n )
440  $ go to 60
441 *
442 * Set KB to the number of columns factorized
443 *
444  kb = n - k
445 *
446  ELSE
447 *
448 * Factorize the leading columns of A using the lower triangle
449 * of A and working forwards, and compute the matrix W = L21*D
450 * for use in updating A22
451 *
452 * K is the main loop index, increasing from 1 in steps of 1 or 2
453 *
454  k = 1
455  70 continue
456 *
457 * Exit from loop
458 *
459  IF( ( k.GE.nb .AND. nb.LT.n ) .OR. k.GT.n )
460  $ go to 90
461 *
462 * Copy column K of A to column K of W and update it
463 *
464  CALL zcopy( n-k+1, a( k, k ), 1, w( k, k ), 1 )
465  CALL zgemv( 'No transpose', n-k+1, k-1, -cone, a( k, 1 ), lda,
466  $ w( k, 1 ), ldw, cone, w( k, k ), 1 )
467 *
468  kstep = 1
469 *
470 * Determine rows and columns to be interchanged and whether
471 * a 1-by-1 or 2-by-2 pivot block will be used
472 *
473  absakk = cabs1( w( k, k ) )
474 *
475 * IMAX is the row-index of the largest off-diagonal element in
476 * column K, and COLMAX is its absolute value
477 *
478  IF( k.LT.n ) THEN
479  imax = k + izamax( n-k, w( k+1, k ), 1 )
480  colmax = cabs1( w( imax, k ) )
481  ELSE
482  colmax = zero
483  END IF
484 *
485  IF( max( absakk, colmax ).EQ.zero ) THEN
486 *
487 * Column K is zero: set INFO and continue
488 *
489  IF( info.EQ.0 )
490  $ info = k
491  kp = k
492  ELSE
493  IF( absakk.GE.alpha*colmax ) THEN
494 *
495 * no interchange, use 1-by-1 pivot block
496 *
497  kp = k
498  ELSE
499 *
500 * Copy column IMAX to column K+1 of W and update it
501 *
502  CALL zcopy( imax-k, a( imax, k ), lda, w( k, k+1 ), 1 )
503  CALL zcopy( n-imax+1, a( imax, imax ), 1, w( imax, k+1 ),
504  $ 1 )
505  CALL zgemv( 'No transpose', n-k+1, k-1, -cone, a( k, 1 ),
506  $ lda, w( imax, 1 ), ldw, cone, w( k, k+1 ),
507  $ 1 )
508 *
509 * JMAX is the column-index of the largest off-diagonal
510 * element in row IMAX, and ROWMAX is its absolute value
511 *
512  jmax = k - 1 + izamax( imax-k, w( k, k+1 ), 1 )
513  rowmax = cabs1( w( jmax, k+1 ) )
514  IF( imax.LT.n ) THEN
515  jmax = imax + izamax( n-imax, w( imax+1, k+1 ), 1 )
516  rowmax = max( rowmax, cabs1( w( jmax, k+1 ) ) )
517  END IF
518 *
519  IF( absakk.GE.alpha*colmax*( colmax / rowmax ) ) THEN
520 *
521 * no interchange, use 1-by-1 pivot block
522 *
523  kp = k
524  ELSE IF( cabs1( w( imax, k+1 ) ).GE.alpha*rowmax ) THEN
525 *
526 * interchange rows and columns K and IMAX, use 1-by-1
527 * pivot block
528 *
529  kp = imax
530 *
531 * copy column K+1 of W to column K
532 *
533  CALL zcopy( n-k+1, w( k, k+1 ), 1, w( k, k ), 1 )
534  ELSE
535 *
536 * interchange rows and columns K+1 and IMAX, use 2-by-2
537 * pivot block
538 *
539  kp = imax
540  kstep = 2
541  END IF
542  END IF
543 *
544  kk = k + kstep - 1
545 *
546 * Updated column KP is already stored in column KK of W
547 *
548  IF( kp.NE.kk ) THEN
549 *
550 * Copy non-updated column KK to column KP
551 *
552  a( kp, k ) = a( kk, k )
553  CALL zcopy( kp-k-1, a( k+1, kk ), 1, a( kp, k+1 ), lda )
554  CALL zcopy( n-kp+1, a( kp, kk ), 1, a( kp, kp ), 1 )
555 *
556 * Interchange rows KK and KP in first KK columns of A and W
557 *
558  CALL zswap( kk, a( kk, 1 ), lda, a( kp, 1 ), lda )
559  CALL zswap( kk, w( kk, 1 ), ldw, w( kp, 1 ), ldw )
560  END IF
561 *
562  IF( kstep.EQ.1 ) THEN
563 *
564 * 1-by-1 pivot block D(k): column k of W now holds
565 *
566 * W(k) = L(k)*D(k)
567 *
568 * where L(k) is the k-th column of L
569 *
570 * Store L(k) in column k of A
571 *
572  CALL zcopy( n-k+1, w( k, k ), 1, a( k, k ), 1 )
573  IF( k.LT.n ) THEN
574  r1 = cone / a( k, k )
575  CALL zscal( n-k, r1, a( k+1, k ), 1 )
576  END IF
577  ELSE
578 *
579 * 2-by-2 pivot block D(k): columns k and k+1 of W now hold
580 *
581 * ( W(k) W(k+1) ) = ( L(k) L(k+1) )*D(k)
582 *
583 * where L(k) and L(k+1) are the k-th and (k+1)-th columns
584 * of L
585 *
586  IF( k.LT.n-1 ) THEN
587 *
588 * Store L(k) and L(k+1) in columns k and k+1 of A
589 *
590  d21 = w( k+1, k )
591  d11 = w( k+1, k+1 ) / d21
592  d22 = w( k, k ) / d21
593  t = cone / ( d11*d22-cone )
594  d21 = t / d21
595  DO 80 j = k + 2, n
596  a( j, k ) = d21*( d11*w( j, k )-w( j, k+1 ) )
597  a( j, k+1 ) = d21*( d22*w( j, k+1 )-w( j, k ) )
598  80 continue
599  END IF
600 *
601 * Copy D(k) to A
602 *
603  a( k, k ) = w( k, k )
604  a( k+1, k ) = w( k+1, k )
605  a( k+1, k+1 ) = w( k+1, k+1 )
606  END IF
607  END IF
608 *
609 * Store details of the interchanges in IPIV
610 *
611  IF( kstep.EQ.1 ) THEN
612  ipiv( k ) = kp
613  ELSE
614  ipiv( k ) = -kp
615  ipiv( k+1 ) = -kp
616  END IF
617 *
618 * Increase K and return to the start of the main loop
619 *
620  k = k + kstep
621  go to 70
622 *
623  90 continue
624 *
625 * Update the lower triangle of A22 (= A(k:n,k:n)) as
626 *
627 * A22 := A22 - L21*D*L21**T = A22 - L21*W**T
628 *
629 * computing blocks of NB columns at a time
630 *
631  DO 110 j = k, n, nb
632  jb = min( nb, n-j+1 )
633 *
634 * Update the lower triangle of the diagonal block
635 *
636  DO 100 jj = j, j + jb - 1
637  CALL zgemv( 'No transpose', j+jb-jj, k-1, -cone,
638  $ a( jj, 1 ), lda, w( jj, 1 ), ldw, cone,
639  $ a( jj, jj ), 1 )
640  100 continue
641 *
642 * Update the rectangular subdiagonal block
643 *
644  IF( j+jb.LE.n )
645  $ CALL zgemm( 'No transpose', 'Transpose', n-j-jb+1, jb,
646  $ k-1, -cone, a( j+jb, 1 ), lda, w( j, 1 ),
647  $ ldw, cone, a( j+jb, j ), lda )
648  110 continue
649 *
650 * Put L21 in standard form by partially undoing the interchanges
651 * in columns 1:k-1
652 *
653  j = k - 1
654  120 continue
655  jj = j
656  jp = ipiv( j )
657  IF( jp.LT.0 ) THEN
658  jp = -jp
659  j = j - 1
660  END IF
661  j = j - 1
662  IF( jp.NE.jj .AND. j.GE.1 )
663  $ CALL zswap( j, a( jp, 1 ), lda, a( jj, 1 ), lda )
664  IF( j.GE.1 )
665  $ go to 120
666 *
667 * Set KB to the number of columns factorized
668 *
669  kb = k - 1
670 *
671  END IF
672  return
673 *
674 * End of ZLASYF
675 *
676  END