LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
clavsy_rook.f
Go to the documentation of this file.
1 *> \brief \b CLAVSY_ROOK
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE CLAVSY_ROOK( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
12 * LDB, INFO )
13 *
14 * .. Scalar Arguments ..
15 * CHARACTER DIAG, TRANS, UPLO
16 * INTEGER INFO, LDA, LDB, N, NRHS
17 * ..
18 * .. Array Arguments ..
19 * INTEGER IPIV( * )
20 * COMPLEX A( LDA, * ), B( LDB, * )
21 * ..
22 *
23 *
24 *> \par Purpose:
25 * =============
26 *>
27 *> \verbatim
28 *>
29 *> CLAVSY_ROOK performs one of the matrix-vector operations
30 *> x := A*x or x := A'*x,
31 *> where x is an N element vector and A is one of the factors
32 *> from the block U*D*U' or L*D*L' factorization computed by CSYTRF_ROOK.
33 *>
34 *> If TRANS = 'N', multiplies by U or U * D (or L or L * D)
35 *> If TRANS = 'T', multiplies by U' or D * U' (or L' or D * L')
36 *> \endverbatim
37 *
38 * Arguments:
39 * ==========
40 *
41 *> \param[in] UPLO
42 *> \verbatim
43 *> UPLO is CHARACTER*1
44 *> Specifies whether the factor stored in A is upper or lower
45 *> triangular.
46 *> = 'U': Upper triangular
47 *> = 'L': Lower triangular
48 *> \endverbatim
49 *>
50 *> \param[in] TRANS
51 *> \verbatim
52 *> TRANS is CHARACTER*1
53 *> Specifies the operation to be performed:
54 *> = 'N': x := A*x
55 *> = 'T': x := A'*x
56 *> \endverbatim
57 *>
58 *> \param[in] DIAG
59 *> \verbatim
60 *> DIAG is CHARACTER*1
61 *> Specifies whether or not the diagonal blocks are unit
62 *> matrices. If the diagonal blocks are assumed to be unit,
63 *> then A = U or A = L, otherwise A = U*D or A = L*D.
64 *> = 'U': Diagonal blocks are assumed to be unit matrices.
65 *> = 'N': Diagonal blocks are assumed to be non-unit matrices.
66 *> \endverbatim
67 *>
68 *> \param[in] N
69 *> \verbatim
70 *> N is INTEGER
71 *> The number of rows and columns of the matrix A. N >= 0.
72 *> \endverbatim
73 *>
74 *> \param[in] NRHS
75 *> \verbatim
76 *> NRHS is INTEGER
77 *> The number of right hand sides, i.e., the number of vectors
78 *> x to be multiplied by A. NRHS >= 0.
79 *> \endverbatim
80 *>
81 *> \param[in] A
82 *> \verbatim
83 *> A is COMPLEX array, dimension (LDA,N)
84 *> The block diagonal matrix D and the multipliers used to
85 *> obtain the factor U or L as computed by CSYTRF_ROOK.
86 *> Stored as a 2-D triangular matrix.
87 *> \endverbatim
88 *>
89 *> \param[in] LDA
90 *> \verbatim
91 *> LDA is INTEGER
92 *> The leading dimension of the array A. LDA >= max(1,N).
93 *> \endverbatim
94 *>
95 *> \param[in] IPIV
96 *> \verbatim
97 *> IPIV is INTEGER array, dimension (N)
98 *> Details of the interchanges and the block structure of D,
99 *> as determined by CSYTRF_ROOK.
100 *>
101 *> If UPLO = 'U':
102 *> If IPIV(k) > 0, then rows and columns k and IPIV(k)
103 *> were interchanged and D(k,k) is a 1-by-1 diagonal block.
104 *> (If IPIV( k ) = k, no interchange was done).
105 *>
106 *> If IPIV(k) < 0 and IPIV(k-1) < 0, then rows and
107 *> columns k and -IPIV(k) were interchanged and rows and
108 *> columns k-1 and -IPIV(k-1) were inerchaged,
109 *> D(k-1:k,k-1:k) is a 2-by-2 diagonal block.
110 *>
111 *> If UPLO = 'L':
112 *> If IPIV(k) > 0, then rows and columns k and IPIV(k)
113 *> were interchanged and D(k,k) is a 1-by-1 diagonal block.
114 *> (If IPIV( k ) = k, no interchange was done).
115 *>
116 *> If IPIV(k) < 0 and IPIV(k+1) < 0, then rows and
117 *> columns k and -IPIV(k) were interchanged and rows and
118 *> columns k+1 and -IPIV(k+1) were inerchaged,
119 *> D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
120 *> \endverbatim
121 *>
122 *> \param[in,out] B
123 *> \verbatim
124 *> B is COMPLEX array, dimension (LDB,NRHS)
125 *> On entry, B contains NRHS vectors of length N.
126 *> On exit, B is overwritten with the product A * B.
127 *> \endverbatim
128 *>
129 *> \param[in] LDB
130 *> \verbatim
131 *> LDB is INTEGER
132 *> The leading dimension of the array B. LDB >= max(1,N).
133 *> \endverbatim
134 *>
135 *> \param[out] INFO
136 *> \verbatim
137 *> INFO is INTEGER
138 *> = 0: successful exit
139 *> < 0: if INFO = -k, the k-th argument had an illegal value
140 *> \endverbatim
141 *
142 * Authors:
143 * ========
144 *
145 *> \author Univ. of Tennessee
146 *> \author Univ. of California Berkeley
147 *> \author Univ. of Colorado Denver
148 *> \author NAG Ltd.
149 *
150 *> \date November 2013
151 *
152 *> \ingroup complex_lin
153 *
154 * =====================================================================
155  SUBROUTINE clavsy_rook( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV,
156  $ b, ldb, info )
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 A( lda, * ), B( ldb, * )
170 * ..
171 *
172 * =====================================================================
173 *
174 * .. Parameters ..
175  COMPLEX CONE
176  parameter ( cone = ( 1.0e+0, 0.0e+0 ) )
177 * ..
178 * .. Local Scalars ..
179  LOGICAL NOUNIT
180  INTEGER J, K, KP
181  COMPLEX D11, D12, D21, D22, T1, T2
182 * ..
183 * .. External Functions ..
184  LOGICAL LSAME
185  EXTERNAL lsame
186 * ..
187 * .. External Subroutines ..
188  EXTERNAL cgemv, cgeru, cscal, cswap, xerbla
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( 'CLAVSY_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 cscal( 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 cgeru( 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 cswap( 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 cgeru( k-1, nrhs, cone, a( 1, k ), 1, b( k, 1 ),
293  $ ldb, b( 1, 1 ), ldb )
294  CALL cgeru( 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 cswap( 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 cswap( 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 cscal( 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 cgeru( 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 cswap( 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 cgeru( n-k, nrhs, cone, a( k+1, k ), 1,
386  $ b( k, 1 ), ldb, b( k+1, 1 ), ldb )
387  CALL cgeru( 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 cswap( 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 cswap( 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 IF( k.LT.1 )
428  $ GO TO 90
429 *
430 * 1 x 1 pivot block.
431 *
432  IF( ipiv( k ).GT.0 ) THEN
433  IF( k.GT.1 ) THEN
434 *
435 * Interchange if P(K) != I.
436 *
437  kp = ipiv( k )
438  IF( kp.NE.k )
439  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
440 *
441 * Apply the transformation
442 *
443  CALL cgemv( 'Transpose', k-1, nrhs, cone, b, ldb,
444  $ a( 1, k ), 1, cone, b( k, 1 ), ldb )
445  END IF
446  IF( nounit )
447  $ CALL cscal( nrhs, a( k, k ), b( k, 1 ), ldb )
448  k = k - 1
449 *
450 * 2 x 2 pivot block.
451 *
452  ELSE
453  IF( k.GT.2 ) THEN
454 *
455 * Swap the second of pair with Pth
456 *
457  kp = abs( ipiv( k ) )
458  IF( kp.NE.k )
459  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
460 *
461 * Now swap the first of pair with IMAX(r)th
462 *
463  kp = abs( ipiv( k-1 ) )
464  IF( kp.NE.k-1 )
465  $ CALL cswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ),
466  $ ldb )
467 *
468 * Apply the transformations
469 *
470  CALL cgemv( 'Transpose', k-2, nrhs, cone, b, ldb,
471  $ a( 1, k ), 1, cone, b( k, 1 ), ldb )
472  CALL cgemv( 'Transpose', k-2, nrhs, cone, b, ldb,
473  $ a( 1, k-1 ), 1, cone, b( k-1, 1 ), ldb )
474  END IF
475 *
476 * Multiply by the diagonal block if non-unit.
477 *
478  IF( nounit ) THEN
479  d11 = a( k-1, k-1 )
480  d22 = a( k, k )
481  d12 = a( k-1, k )
482  d21 = d12
483  DO 80 j = 1, nrhs
484  t1 = b( k-1, j )
485  t2 = b( k, j )
486  b( k-1, j ) = d11*t1 + d12*t2
487  b( k, j ) = d21*t1 + d22*t2
488  80 CONTINUE
489  END IF
490  k = k - 2
491  END IF
492  GO TO 70
493  90 CONTINUE
494 *
495 * Form B := L'*B
496 * where L = P(1)*inv(L(1))* ... *P(m)*inv(L(m))
497 * and L' = inv(L'(m))*P(m)* ... *inv(L'(1))*P(1)
498 *
499  ELSE
500 *
501 * Loop forward applying the L-transformations.
502 *
503  k = 1
504  100 CONTINUE
505  IF( k.GT.n )
506  $ GO TO 120
507 *
508 * 1 x 1 pivot block
509 *
510  IF( ipiv( k ).GT.0 ) THEN
511  IF( k.LT.n ) THEN
512 *
513 * Interchange if P(K) != I.
514 *
515  kp = ipiv( k )
516  IF( kp.NE.k )
517  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
518 *
519 * Apply the transformation
520 *
521  CALL cgemv( 'Transpose', n-k, nrhs, cone, b( k+1, 1 ),
522  $ ldb, a( k+1, k ), 1, cone, b( k, 1 ), ldb )
523  END IF
524  IF( nounit )
525  $ CALL cscal( nrhs, a( k, k ), b( k, 1 ), ldb )
526  k = k + 1
527 *
528 * 2 x 2 pivot block.
529 *
530  ELSE
531  IF( k.LT.n-1 ) THEN
532 *
533 * Swap the first of pair with Pth
534 *
535  kp = abs( ipiv( k ) )
536  IF( kp.NE.k )
537  $ CALL cswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
538 *
539 * Now swap the second of pair with IMAX(r)th
540 *
541  kp = abs( ipiv( k+1 ) )
542  IF( kp.NE.k+1 )
543  $ CALL cswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ),
544  $ ldb )
545 *
546 * Apply the transformation
547 *
548  CALL cgemv( 'Transpose', n-k-1, nrhs, cone,
549  $ b( k+2, 1 ), ldb, a( k+2, k+1 ), 1, cone,
550  $ b( k+1, 1 ), ldb )
551  CALL cgemv( 'Transpose', n-k-1, nrhs, cone,
552  $ b( k+2, 1 ), ldb, a( k+2, k ), 1, cone,
553  $ b( k, 1 ), ldb )
554  END IF
555 *
556 * Multiply by the diagonal block if non-unit.
557 *
558  IF( nounit ) THEN
559  d11 = a( k, k )
560  d22 = a( k+1, k+1 )
561  d21 = a( k+1, k )
562  d12 = d21
563  DO 110 j = 1, nrhs
564  t1 = b( k, j )
565  t2 = b( k+1, j )
566  b( k, j ) = d11*t1 + d12*t2
567  b( k+1, j ) = d21*t1 + d22*t2
568  110 CONTINUE
569  END IF
570  k = k + 2
571  END IF
572  GO TO 100
573  120 CONTINUE
574  END IF
575  END IF
576  RETURN
577 *
578 * End of CLAVSY_ROOK
579 *
580  END
subroutine clavsy_rook(UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B, LDB, INFO)
CLAVSY_ROOK
Definition: clavsy_rook.f:157
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cscal(N, CA, CX, INCX)
CSCAL
Definition: cscal.f:54
subroutine cgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
CGEMV
Definition: cgemv.f:160
subroutine cswap(N, CX, INCX, CY, INCY)
CSWAP
Definition: cswap.f:52
subroutine cgeru(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)
CGERU
Definition: cgeru.f:132