LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zlavsy_rook ( character  UPLO,
character  TRANS,
character  DIAG,
integer  N,
integer  NRHS,
complex*16, dimension( lda, * )  A,
integer  LDA,
integer, dimension( * )  IPIV,
complex*16, dimension( ldb, * )  B,
integer  LDB,
integer  INFO 
)

ZLAVSY_ROOK

Purpose:
 ZLAVSY_ROOK performs one of the matrix-vector operations
    x := A*x  or  x := A'*x,
 where x is an N element vector and  A is one of the factors
 from the block U*D*U' or L*D*L' factorization computed by ZSYTRF_ROOK.

 If TRANS = 'N', multiplies by U  or U * D  (or L  or L * D)
 If TRANS = 'T', multiplies by U' or D * U' (or L' or D * L')
Parameters
[in]UPLO
          UPLO is CHARACTER*1
          Specifies whether the factor stored in A is upper or lower
          triangular.
          = 'U':  Upper triangular
          = 'L':  Lower triangular
[in]TRANS
          TRANS is CHARACTER*1
          Specifies the operation to be performed:
          = 'N':  x := A*x
          = 'T':  x := A'*x
[in]DIAG
          DIAG is CHARACTER*1
          Specifies whether or not the diagonal blocks are unit
          matrices.  If the diagonal blocks are assumed to be unit,
          then A = U or A = L, otherwise A = U*D or A = L*D.
          = 'U':  Diagonal blocks are assumed to be unit matrices.
          = 'N':  Diagonal blocks are assumed to be non-unit matrices.
[in]N
          N is INTEGER
          The number of rows and columns of the matrix A.  N >= 0.
[in]NRHS
          NRHS is INTEGER
          The number of right hand sides, i.e., the number of vectors
          x to be multiplied by A.  NRHS >= 0.
[in]A
          A is COMPLEX*16 array, dimension (LDA,N)
          The block diagonal matrix D and the multipliers used to
          obtain the factor U or L as computed by ZSYTRF_ROOK.
          Stored as a 2-D triangular matrix.
[in]LDA
          LDA is INTEGER
          The leading dimension of the array A.  LDA >= max(1,N).
[in]IPIV
          IPIV is INTEGER array, dimension (N)
          Details of the interchanges and the block structure of D,
          as determined by ZSYTRF_ROOK.

          If UPLO = 'U':
               If IPIV(k) > 0, then rows and columns k and IPIV(k)
               were interchanged and D(k,k) is a 1-by-1 diagonal block.
               (If IPIV( k ) = k, no interchange was done).

               If IPIV(k) < 0 and IPIV(k-1) < 0, then rows and
               columns k and -IPIV(k) were interchanged and rows and
               columns k-1 and -IPIV(k-1) were inerchaged,
               D(k-1:k,k-1:k) is a 2-by-2 diagonal block.

          If UPLO = 'L':
               If IPIV(k) > 0, then rows and columns k and IPIV(k)
               were interchanged and D(k,k) is a 1-by-1 diagonal block.
               (If IPIV( k ) = k, no interchange was done).

               If IPIV(k) < 0 and IPIV(k+1) < 0, then rows and
               columns k and -IPIV(k) were interchanged and rows and
               columns k+1 and -IPIV(k+1) were inerchaged,
               D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
[in,out]B
          B is COMPLEX*16 array, dimension (LDB,NRHS)
          On entry, B contains NRHS vectors of length N.
          On exit, B is overwritten with the product A * B.
[in]LDB
          LDB is INTEGER
          The leading dimension of the array B.  LDB >= max(1,N).
[out]INFO
          INFO is INTEGER
          = 0: successful exit
          < 0: if INFO = -k, the k-th argument had an illegal value
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2013

Definition at line 157 of file zlavsy_rook.f.

157 *
158 * -- LAPACK test routine (version 3.5.0) --
159 * -- LAPACK is a software package provided by Univ. of Tennessee, --
160 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
161 * November 2013
162 *
163 * .. Scalar Arguments ..
164  CHARACTER diag, trans, uplo
165  INTEGER info, lda, ldb, n, nrhs
166 * ..
167 * .. Array Arguments ..
168  INTEGER ipiv( * )
169  COMPLEX*16 a( lda, * ), b( ldb, * )
170 * ..
171 *
172 * =====================================================================
173 *
174 * .. Parameters ..
175  COMPLEX*16 cone
176  parameter ( cone = ( 1.0d+0, 0.0d+0 ) )
177 * ..
178 * .. Local Scalars ..
179  LOGICAL nounit
180  INTEGER j, k, kp
181  COMPLEX*16 d11, d12, d21, d22, t1, t2
182 * ..
183 * .. External Functions ..
184  LOGICAL lsame
185  EXTERNAL lsame
186 * ..
187 * .. External Subroutines ..
188  EXTERNAL xerbla, zgemv, zgeru, zscal, zswap
189 * ..
190 * .. Intrinsic Functions ..
191  INTRINSIC abs, max
192 * ..
193 * .. Executable Statements ..
194 *
195 * Test the input parameters.
196 *
197  info = 0
198  IF( .NOT.lsame( uplo, 'U' ) .AND. .NOT.lsame( uplo, 'L' ) ) THEN
199  info = -1
200  ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.lsame( trans, 'T' ) )
201  $ THEN
202  info = -2
203  ELSE IF( .NOT.lsame( diag, 'U' ) .AND. .NOT.lsame( diag, 'N' ) )
204  $ THEN
205  info = -3
206  ELSE IF( n.LT.0 ) THEN
207  info = -4
208  ELSE IF( lda.LT.max( 1, n ) ) THEN
209  info = -6
210  ELSE IF( ldb.LT.max( 1, n ) ) THEN
211  info = -9
212  END IF
213  IF( info.NE.0 ) THEN
214  CALL xerbla( 'ZLAVSY_ROOK ', -info )
215  RETURN
216  END IF
217 *
218 * Quick return if possible.
219 *
220  IF( n.EQ.0 )
221  $ RETURN
222 *
223  nounit = lsame( diag, 'N' )
224 *------------------------------------------
225 *
226 * Compute B := A * B (No transpose)
227 *
228 *------------------------------------------
229  IF( lsame( trans, 'N' ) ) THEN
230 *
231 * Compute B := U*B
232 * where U = P(m)*inv(U(m))* ... *P(1)*inv(U(1))
233 *
234  IF( lsame( uplo, 'U' ) ) THEN
235 *
236 * Loop forward applying the transformations.
237 *
238  k = 1
239  10 CONTINUE
240  IF( k.GT.n )
241  $ GO TO 30
242  IF( ipiv( k ).GT.0 ) THEN
243 *
244 * 1 x 1 pivot block
245 *
246 * Multiply by the diagonal element if forming U * D.
247 *
248  IF( nounit )
249  $ CALL zscal( nrhs, a( k, k ), b( k, 1 ), ldb )
250 *
251 * Multiply by P(K) * inv(U(K)) if K > 1.
252 *
253  IF( k.GT.1 ) THEN
254 *
255 * Apply the transformation.
256 *
257  CALL zgeru( k-1, nrhs, cone, a( 1, k ), 1, b( k, 1 ),
258  $ ldb, b( 1, 1 ), ldb )
259 *
260 * Interchange if P(K) != I.
261 *
262  kp = ipiv( k )
263  IF( kp.NE.k )
264  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
265  END IF
266  k = k + 1
267  ELSE
268 *
269 * 2 x 2 pivot block
270 *
271 * Multiply by the diagonal block if forming U * D.
272 *
273  IF( nounit ) THEN
274  d11 = a( k, k )
275  d22 = a( k+1, k+1 )
276  d12 = a( k, k+1 )
277  d21 = d12
278  DO 20 j = 1, nrhs
279  t1 = b( k, j )
280  t2 = b( k+1, j )
281  b( k, j ) = d11*t1 + d12*t2
282  b( k+1, j ) = d21*t1 + d22*t2
283  20 CONTINUE
284  END IF
285 *
286 * Multiply by P(K) * inv(U(K)) if K > 1.
287 *
288  IF( k.GT.1 ) THEN
289 *
290 * Apply the transformations.
291 *
292  CALL zgeru( k-1, nrhs, cone, a( 1, k ), 1, b( k, 1 ),
293  $ ldb, b( 1, 1 ), ldb )
294  CALL zgeru( k-1, nrhs, cone, a( 1, k+1 ), 1,
295  $ b( k+1, 1 ), ldb, b( 1, 1 ), ldb )
296 *
297 * Interchange if a permutation was applied at the
298 * K-th step of the factorization.
299 *
300 * Swap the first of pair with IMAXth
301 *
302  kp = abs( ipiv( k ) )
303  IF( kp.NE.k )
304  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
305 *
306 * NOW swap the first of pair with Pth
307 *
308  kp = abs( ipiv( k+1 ) )
309  IF( kp.NE.k+1 )
310  $ CALL zswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ),
311  $ ldb )
312  END IF
313  k = k + 2
314  END IF
315  GO TO 10
316  30 CONTINUE
317 *
318 * Compute B := L*B
319 * where L = P(1)*inv(L(1))* ... *P(m)*inv(L(m)) .
320 *
321  ELSE
322 *
323 * Loop backward applying the transformations to B.
324 *
325  k = n
326  40 CONTINUE
327  IF( k.LT.1 )
328  $ GO TO 60
329 *
330 * Test the pivot index. If greater than zero, a 1 x 1
331 * pivot was used, otherwise a 2 x 2 pivot was used.
332 *
333  IF( ipiv( k ).GT.0 ) THEN
334 *
335 * 1 x 1 pivot block:
336 *
337 * Multiply by the diagonal element if forming L * D.
338 *
339  IF( nounit )
340  $ CALL zscal( nrhs, a( k, k ), b( k, 1 ), ldb )
341 *
342 * Multiply by P(K) * inv(L(K)) if K < N.
343 *
344  IF( k.NE.n ) THEN
345  kp = ipiv( k )
346 *
347 * Apply the transformation.
348 *
349  CALL zgeru( n-k, nrhs, cone, a( k+1, k ), 1,
350  $ b( k, 1 ), ldb, b( k+1, 1 ), ldb )
351 *
352 * Interchange if a permutation was applied at the
353 * K-th step of the factorization.
354 *
355  IF( kp.NE.k )
356  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
357  END IF
358  k = k - 1
359 *
360  ELSE
361 *
362 * 2 x 2 pivot block:
363 *
364 * Multiply by the diagonal block if forming L * D.
365 *
366  IF( nounit ) THEN
367  d11 = a( k-1, k-1 )
368  d22 = a( k, k )
369  d21 = a( k, k-1 )
370  d12 = d21
371  DO 50 j = 1, nrhs
372  t1 = b( k-1, j )
373  t2 = b( k, j )
374  b( k-1, j ) = d11*t1 + d12*t2
375  b( k, j ) = d21*t1 + d22*t2
376  50 CONTINUE
377  END IF
378 *
379 * Multiply by P(K) * inv(L(K)) if K < N.
380 *
381  IF( k.NE.n ) THEN
382 *
383 * Apply the transformation.
384 *
385  CALL zgeru( n-k, nrhs, cone, a( k+1, k ), 1,
386  $ b( k, 1 ), ldb, b( k+1, 1 ), ldb )
387  CALL zgeru( n-k, nrhs, cone, a( k+1, k-1 ), 1,
388  $ b( k-1, 1 ), ldb, b( k+1, 1 ), ldb )
389 *
390 * Interchange if a permutation was applied at the
391 * K-th step of the factorization.
392 *
393 * Swap the second of pair with IMAXth
394 *
395  kp = abs( ipiv( k ) )
396  IF( kp.NE.k )
397  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
398 *
399 * NOW swap the first of pair with Pth
400 *
401  kp = abs( ipiv( k-1 ) )
402  IF( kp.NE.k-1 )
403  $ CALL zswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ),
404  $ ldb )
405  END IF
406  k = k - 2
407  END IF
408  GO TO 40
409  60 CONTINUE
410  END IF
411 *----------------------------------------
412 *
413 * Compute B := A' * B (transpose)
414 *
415 *----------------------------------------
416  ELSE IF( lsame( trans, 'T' ) ) THEN
417 *
418 * Form B := U'*B
419 * where U = P(m)*inv(U(m))* ... *P(1)*inv(U(1))
420 * and U' = inv(U'(1))*P(1)* ... *inv(U'(m))*P(m)
421 *
422  IF( lsame( uplo, 'U' ) ) THEN
423 *
424 * Loop backward applying the transformations.
425 *
426  k = n
427  70 CONTINUE
428  IF( k.LT.1 )
429  $ GO TO 90
430 *
431 * 1 x 1 pivot block.
432 *
433  IF( ipiv( k ).GT.0 ) THEN
434  IF( k.GT.1 ) THEN
435 *
436 * Interchange if P(K) != I.
437 *
438  kp = ipiv( k )
439  IF( kp.NE.k )
440  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
441 *
442 * Apply the transformation
443 *
444  CALL zgemv( 'Transpose', k-1, nrhs, cone, b, ldb,
445  $ a( 1, k ), 1, cone, b( k, 1 ), ldb )
446  END IF
447  IF( nounit )
448  $ CALL zscal( nrhs, a( k, k ), b( k, 1 ), ldb )
449  k = k - 1
450 *
451 * 2 x 2 pivot block.
452 *
453  ELSE
454  IF( k.GT.2 ) THEN
455 *
456 * Swap the second of pair with Pth
457 *
458  kp = abs( ipiv( k ) )
459  IF( kp.NE.k )
460  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
461 *
462 * Now swap the first of pair with IMAX(r)th
463 *
464  kp = abs( ipiv( k-1 ) )
465  IF( kp.NE.k-1 )
466  $ CALL zswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ),
467  $ ldb )
468 *
469 * Apply the transformations
470 *
471  CALL zgemv( 'Transpose', k-2, nrhs, cone, b, ldb,
472  $ a( 1, k ), 1, cone, b( k, 1 ), ldb )
473  CALL zgemv( 'Transpose', k-2, nrhs, cone, b, ldb,
474  $ a( 1, k-1 ), 1, cone, b( k-1, 1 ), ldb )
475  END IF
476 *
477 * Multiply by the diagonal block if non-unit.
478 *
479  IF( nounit ) THEN
480  d11 = a( k-1, k-1 )
481  d22 = a( k, k )
482  d12 = a( k-1, k )
483  d21 = d12
484  DO 80 j = 1, nrhs
485  t1 = b( k-1, j )
486  t2 = b( k, j )
487  b( k-1, j ) = d11*t1 + d12*t2
488  b( k, j ) = d21*t1 + d22*t2
489  80 CONTINUE
490  END IF
491  k = k - 2
492  END IF
493  GO TO 70
494  90 CONTINUE
495 *
496 * Form B := L'*B
497 * where L = P(1)*inv(L(1))* ... *P(m)*inv(L(m))
498 * and L' = inv(L'(m))*P(m)* ... *inv(L'(1))*P(1)
499 *
500  ELSE
501 *
502 * Loop forward applying the L-transformations.
503 *
504  k = 1
505  100 CONTINUE
506  IF( k.GT.n )
507  $ GO TO 120
508 *
509 * 1 x 1 pivot block
510 *
511  IF( ipiv( k ).GT.0 ) THEN
512  IF( k.LT.n ) THEN
513 *
514 * Interchange if P(K) != I.
515 *
516  kp = ipiv( k )
517  IF( kp.NE.k )
518  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
519 *
520 * Apply the transformation
521 *
522  CALL zgemv( 'Transpose', n-k, nrhs, cone, b( k+1, 1 ),
523  $ ldb, a( k+1, k ), 1, cone, b( k, 1 ), ldb )
524  END IF
525  IF( nounit )
526  $ CALL zscal( nrhs, a( k, k ), b( k, 1 ), ldb )
527  k = k + 1
528 *
529 * 2 x 2 pivot block.
530 *
531  ELSE
532  IF( k.LT.n-1 ) THEN
533 *
534 * Swap the first of pair with Pth
535 *
536  kp = abs( ipiv( k ) )
537  IF( kp.NE.k )
538  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
539 *
540 * Now swap the second of pair with IMAX(r)th
541 *
542  kp = abs( ipiv( k+1 ) )
543  IF( kp.NE.k+1 )
544  $ CALL zswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ),
545  $ ldb )
546 *
547 * Apply the transformation
548 *
549  CALL zgemv( 'Transpose', n-k-1, nrhs, cone,
550  $ b( k+2, 1 ), ldb, a( k+2, k+1 ), 1, cone,
551  $ b( k+1, 1 ), ldb )
552  CALL zgemv( 'Transpose', n-k-1, nrhs, cone,
553  $ b( k+2, 1 ), ldb, a( k+2, k ), 1, cone,
554  $ b( k, 1 ), ldb )
555  END IF
556 *
557 * Multiply by the diagonal block if non-unit.
558 *
559  IF( nounit ) THEN
560  d11 = a( k, k )
561  d22 = a( k+1, k+1 )
562  d21 = a( k+1, k )
563  d12 = d21
564  DO 110 j = 1, nrhs
565  t1 = b( k, j )
566  t2 = b( k+1, j )
567  b( k, j ) = d11*t1 + d12*t2
568  b( k+1, j ) = d21*t1 + d22*t2
569  110 CONTINUE
570  END IF
571  k = k + 2
572  END IF
573  GO TO 100
574  120 CONTINUE
575  END IF
576  END IF
577  RETURN
578 *
579 * End of ZLAVSY_ROOK
580 *
subroutine zgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
ZGEMV
Definition: zgemv.f:160
subroutine zswap(N, ZX, INCX, ZY, INCY)
ZSWAP
Definition: zswap.f:52
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine zgeru(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
ZGERU
Definition: zgeru.f:132
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55
subroutine zscal(N, ZA, ZX, INCX)
ZSCAL
Definition: zscal.f:54

Here is the call graph for this function:

Here is the caller graph for this function: