LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zlavsy.f
Go to the documentation of this file.
1 *> \brief \b ZLAVSY
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 ZLAVSY( 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*16 A( LDA, * ), B( LDB, * )
21 * ..
22 *
23 *
24 *> \par Purpose:
25 * =============
26 *>
27 *> \verbatim
28 *>
29 *> ZLAVSY 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 ZSYTRF.
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*16 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 ZSYTRF.
86 *> \endverbatim
87 *>
88 *> \param[in] LDA
89 *> \verbatim
90 *> LDA is INTEGER
91 *> The leading dimension of the array A. LDA >= max(1,N).
92 *> \endverbatim
93 *>
94 *> \param[in] IPIV
95 *> \verbatim
96 *> IPIV is INTEGER array, dimension (N)
97 *> Details of the interchanges and the block structure of D,
98 *> as determined by ZSYTRF or ZHETRF.
99 *>
100 *> If UPLO = 'U':
101 *> If IPIV(k) > 0, then rows and columns k and IPIV(k)
102 *> were interchanged and D(k,k) is a 1-by-1 diagonal block.
103 *> (If IPIV( k ) = k, no interchange was done).
104 *>
105 *> If IPIV(k) = IPIV(k-1) < 0, then rows and
106 *> columns k-1 and -IPIV(k) were interchanged,
107 *> D(k-1:k,k-1:k) is a 2-by-2 diagonal block.
108 *>
109 *> If UPLO = 'L':
110 *> If IPIV(k) > 0, then rows and columns k and IPIV(k)
111 *> were interchanged and D(k,k) is a 1-by-1 diagonal block.
112 *> (If IPIV( k ) = k, no interchange was done).
113 *>
114 *> If IPIV(k) = IPIV(k+1) < 0, then rows and
115 *> columns k+1 and -IPIV(k) were interchanged,
116 *> D(k:k+1,k:k+1) is a 2-by-2 diagonal block.
117 *> \endverbatim
118 *>
119 *> \param[in,out] B
120 *> \verbatim
121 *> B is COMPLEX*16 array, dimension (LDB,NRHS)
122 *> On entry, B contains NRHS vectors of length N.
123 *> On exit, B is overwritten with the product A * B.
124 *> \endverbatim
125 *>
126 *> \param[in] LDB
127 *> \verbatim
128 *> LDB is INTEGER
129 *> The leading dimension of the array B. LDB >= max(1,N).
130 *> \endverbatim
131 *>
132 *> \param[out] INFO
133 *> \verbatim
134 *> INFO is INTEGER
135 *> = 0: successful exit
136 *> < 0: if INFO = -k, the k-th argument had an illegal value
137 *> \endverbatim
138 *
139 * Authors:
140 * ========
141 *
142 *> \author Univ. of Tennessee
143 *> \author Univ. of California Berkeley
144 *> \author Univ. of Colorado Denver
145 *> \author NAG Ltd.
146 *
147 *> \date April 2012
148 *
149 *> \ingroup complex16_lin
150 *
151 * =====================================================================
152  SUBROUTINE zlavsy( UPLO, TRANS, DIAG, N, NRHS, A, LDA, IPIV, B,
153  $ ldb, info )
154 *
155 * -- LAPACK test routine (version 3.4.1) --
156 * -- LAPACK is a software package provided by Univ. of Tennessee, --
157 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
158 * April 2012
159 *
160 * .. Scalar Arguments ..
161  CHARACTER diag, trans, uplo
162  INTEGER info, lda, ldb, n, nrhs
163 * ..
164 * .. Array Arguments ..
165  INTEGER ipiv( * )
166  COMPLEX*16 a( lda, * ), b( ldb, * )
167 * ..
168 *
169 * =====================================================================
170 *
171 * .. Parameters ..
172  COMPLEX*16 cone
173  parameter( cone = ( 1.0d+0, 0.0d+0 ) )
174 * ..
175 * .. Local Scalars ..
176  LOGICAL nounit
177  INTEGER j, k, kp
178  COMPLEX*16 d11, d12, d21, d22, t1, t2
179 * ..
180 * .. External Functions ..
181  LOGICAL lsame
182  EXTERNAL lsame
183 * ..
184 * .. External Subroutines ..
185  EXTERNAL xerbla, zgemv, zgeru, zscal, zswap
186 * ..
187 * .. Intrinsic Functions ..
188  INTRINSIC abs, max
189 * ..
190 * .. Executable Statements ..
191 *
192 * Test the input parameters.
193 *
194  info = 0
195  IF( .NOT.lsame( uplo, 'U' ) .AND. .NOT.lsame( uplo, 'L' ) ) THEN
196  info = -1
197  ELSE IF( .NOT.lsame( trans, 'N' ) .AND. .NOT.lsame( trans, 'T' ) )
198  $ THEN
199  info = -2
200  ELSE IF( .NOT.lsame( diag, 'U' ) .AND. .NOT.lsame( diag, 'N' ) )
201  $ THEN
202  info = -3
203  ELSE IF( n.LT.0 ) THEN
204  info = -4
205  ELSE IF( lda.LT.max( 1, n ) ) THEN
206  info = -6
207  ELSE IF( ldb.LT.max( 1, n ) ) THEN
208  info = -9
209  END IF
210  IF( info.NE.0 ) THEN
211  CALL xerbla( 'ZLAVSY ', -info )
212  return
213  END IF
214 *
215 * Quick return if possible.
216 *
217  IF( n.EQ.0 )
218  $ return
219 *
220  nounit = lsame( diag, 'N' )
221 *------------------------------------------
222 *
223 * Compute B := A * B (No transpose)
224 *
225 *------------------------------------------
226  IF( lsame( trans, 'N' ) ) THEN
227 *
228 * Compute B := U*B
229 * where U = P(m)*inv(U(m))* ... *P(1)*inv(U(1))
230 *
231  IF( lsame( uplo, 'U' ) ) THEN
232 *
233 * Loop forward applying the transformations.
234 *
235  k = 1
236  10 continue
237  IF( k.GT.n )
238  $ go to 30
239  IF( ipiv( k ).GT.0 ) THEN
240 *
241 * 1 x 1 pivot block
242 *
243 * Multiply by the diagonal element if forming U * D.
244 *
245  IF( nounit )
246  $ CALL zscal( nrhs, a( k, k ), b( k, 1 ), ldb )
247 *
248 * Multiply by P(K) * inv(U(K)) if K > 1.
249 *
250  IF( k.GT.1 ) THEN
251 *
252 * Apply the transformation.
253 *
254  CALL zgeru( k-1, nrhs, cone, a( 1, k ), 1, b( k, 1 ),
255  $ ldb, b( 1, 1 ), ldb )
256 *
257 * Interchange if P(K) != I.
258 *
259  kp = ipiv( k )
260  IF( kp.NE.k )
261  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
262  END IF
263  k = k + 1
264  ELSE
265 *
266 * 2 x 2 pivot block
267 *
268 * Multiply by the diagonal block if forming U * D.
269 *
270  IF( nounit ) THEN
271  d11 = a( k, k )
272  d22 = a( k+1, k+1 )
273  d12 = a( k, k+1 )
274  d21 = d12
275  DO 20 j = 1, nrhs
276  t1 = b( k, j )
277  t2 = b( k+1, j )
278  b( k, j ) = d11*t1 + d12*t2
279  b( k+1, j ) = d21*t1 + d22*t2
280  20 continue
281  END IF
282 *
283 * Multiply by P(K) * inv(U(K)) if K > 1.
284 *
285  IF( k.GT.1 ) THEN
286 *
287 * Apply the transformations.
288 *
289  CALL zgeru( k-1, nrhs, cone, a( 1, k ), 1, b( k, 1 ),
290  $ ldb, b( 1, 1 ), ldb )
291  CALL zgeru( k-1, nrhs, cone, a( 1, k+1 ), 1,
292  $ b( k+1, 1 ), ldb, b( 1, 1 ), ldb )
293 *
294 * Interchange if P(K) != I.
295 *
296  kp = abs( ipiv( k ) )
297  IF( kp.NE.k )
298  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
299  END IF
300  k = k + 2
301  END IF
302  go to 10
303  30 continue
304 *
305 * Compute B := L*B
306 * where L = P(1)*inv(L(1))* ... *P(m)*inv(L(m)) .
307 *
308  ELSE
309 *
310 * Loop backward applying the transformations to B.
311 *
312  k = n
313  40 continue
314  IF( k.LT.1 )
315  $ go to 60
316 *
317 * Test the pivot index. If greater than zero, a 1 x 1
318 * pivot was used, otherwise a 2 x 2 pivot was used.
319 *
320  IF( ipiv( k ).GT.0 ) THEN
321 *
322 * 1 x 1 pivot block:
323 *
324 * Multiply by the diagonal element if forming L * D.
325 *
326  IF( nounit )
327  $ CALL zscal( nrhs, a( k, k ), b( k, 1 ), ldb )
328 *
329 * Multiply by P(K) * inv(L(K)) if K < N.
330 *
331  IF( k.NE.n ) THEN
332  kp = ipiv( k )
333 *
334 * Apply the transformation.
335 *
336  CALL zgeru( n-k, nrhs, cone, a( k+1, k ), 1,
337  $ b( k, 1 ), ldb, b( k+1, 1 ), ldb )
338 *
339 * Interchange if a permutation was applied at the
340 * K-th step of the factorization.
341 *
342  IF( kp.NE.k )
343  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
344  END IF
345  k = k - 1
346 *
347  ELSE
348 *
349 * 2 x 2 pivot block:
350 *
351 * Multiply by the diagonal block if forming L * D.
352 *
353  IF( nounit ) THEN
354  d11 = a( k-1, k-1 )
355  d22 = a( k, k )
356  d21 = a( k, k-1 )
357  d12 = d21
358  DO 50 j = 1, nrhs
359  t1 = b( k-1, j )
360  t2 = b( k, j )
361  b( k-1, j ) = d11*t1 + d12*t2
362  b( k, j ) = d21*t1 + d22*t2
363  50 continue
364  END IF
365 *
366 * Multiply by P(K) * inv(L(K)) if K < N.
367 *
368  IF( k.NE.n ) THEN
369 *
370 * Apply the transformation.
371 *
372  CALL zgeru( n-k, nrhs, cone, a( k+1, k ), 1,
373  $ b( k, 1 ), ldb, b( k+1, 1 ), ldb )
374  CALL zgeru( n-k, nrhs, cone, a( k+1, k-1 ), 1,
375  $ b( k-1, 1 ), ldb, b( k+1, 1 ), ldb )
376 *
377 * Interchange if a permutation was applied at the
378 * K-th step of the factorization.
379 *
380  kp = abs( ipiv( k ) )
381  IF( kp.NE.k )
382  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
383  END IF
384  k = k - 2
385  END IF
386  go to 40
387  60 continue
388  END IF
389 *----------------------------------------
390 *
391 * Compute B := A' * B (transpose)
392 *
393 *----------------------------------------
394  ELSE IF( lsame( trans, 'T' ) ) THEN
395 *
396 * Form B := U'*B
397 * where U = P(m)*inv(U(m))* ... *P(1)*inv(U(1))
398 * and U' = inv(U'(1))*P(1)* ... *inv(U'(m))*P(m)
399 *
400  IF( lsame( uplo, 'U' ) ) THEN
401 *
402 * Loop backward applying the transformations.
403 *
404  k = n
405  70 continue
406  IF( k.LT.1 )
407  $ go to 90
408 *
409 * 1 x 1 pivot block.
410 *
411  IF( ipiv( k ).GT.0 ) THEN
412  IF( k.GT.1 ) THEN
413 *
414 * Interchange if P(K) != I.
415 *
416  kp = ipiv( k )
417  IF( kp.NE.k )
418  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
419 *
420 * Apply the transformation
421 *
422  CALL zgemv( 'Transpose', k-1, nrhs, cone, b, ldb,
423  $ a( 1, k ), 1, cone, b( k, 1 ), ldb )
424  END IF
425  IF( nounit )
426  $ CALL zscal( nrhs, a( k, k ), b( k, 1 ), ldb )
427  k = k - 1
428 *
429 * 2 x 2 pivot block.
430 *
431  ELSE
432  IF( k.GT.2 ) THEN
433 *
434 * Interchange if P(K) != I.
435 *
436  kp = abs( ipiv( k ) )
437  IF( kp.NE.k-1 )
438  $ CALL zswap( nrhs, b( k-1, 1 ), ldb, b( kp, 1 ),
439  $ ldb )
440 *
441 * Apply the transformations
442 *
443  CALL zgemv( 'Transpose', k-2, nrhs, cone, b, ldb,
444  $ a( 1, k ), 1, cone, b( k, 1 ), ldb )
445  CALL zgemv( 'Transpose', k-2, nrhs, cone, b, ldb,
446  $ a( 1, k-1 ), 1, cone, b( k-1, 1 ), ldb )
447  END IF
448 *
449 * Multiply by the diagonal block if non-unit.
450 *
451  IF( nounit ) THEN
452  d11 = a( k-1, k-1 )
453  d22 = a( k, k )
454  d12 = a( k-1, k )
455  d21 = d12
456  DO 80 j = 1, nrhs
457  t1 = b( k-1, j )
458  t2 = b( k, j )
459  b( k-1, j ) = d11*t1 + d12*t2
460  b( k, j ) = d21*t1 + d22*t2
461  80 continue
462  END IF
463  k = k - 2
464  END IF
465  go to 70
466  90 continue
467 *
468 * Form B := L'*B
469 * where L = P(1)*inv(L(1))* ... *P(m)*inv(L(m))
470 * and L' = inv(L'(m))*P(m)* ... *inv(L'(1))*P(1)
471 *
472  ELSE
473 *
474 * Loop forward applying the L-transformations.
475 *
476  k = 1
477  100 continue
478  IF( k.GT.n )
479  $ go to 120
480 *
481 * 1 x 1 pivot block
482 *
483  IF( ipiv( k ).GT.0 ) THEN
484  IF( k.LT.n ) THEN
485 *
486 * Interchange if P(K) != I.
487 *
488  kp = ipiv( k )
489  IF( kp.NE.k )
490  $ CALL zswap( nrhs, b( k, 1 ), ldb, b( kp, 1 ), ldb )
491 *
492 * Apply the transformation
493 *
494  CALL zgemv( 'Transpose', n-k, nrhs, cone, b( k+1, 1 ),
495  $ ldb, a( k+1, k ), 1, cone, b( k, 1 ), ldb )
496  END IF
497  IF( nounit )
498  $ CALL zscal( nrhs, a( k, k ), b( k, 1 ), ldb )
499  k = k + 1
500 *
501 * 2 x 2 pivot block.
502 *
503  ELSE
504  IF( k.LT.n-1 ) THEN
505 *
506 * Interchange if P(K) != I.
507 *
508  kp = abs( ipiv( k ) )
509  IF( kp.NE.k+1 )
510  $ CALL zswap( nrhs, b( k+1, 1 ), ldb, b( kp, 1 ),
511  $ ldb )
512 *
513 * Apply the transformation
514 *
515  CALL zgemv( 'Transpose', n-k-1, nrhs, cone,
516  $ b( k+2, 1 ), ldb, a( k+2, k+1 ), 1, cone,
517  $ b( k+1, 1 ), ldb )
518  CALL zgemv( 'Transpose', n-k-1, nrhs, cone,
519  $ b( k+2, 1 ), ldb, a( k+2, k ), 1, cone,
520  $ b( k, 1 ), ldb )
521  END IF
522 *
523 * Multiply by the diagonal block if non-unit.
524 *
525  IF( nounit ) THEN
526  d11 = a( k, k )
527  d22 = a( k+1, k+1 )
528  d21 = a( k+1, k )
529  d12 = d21
530  DO 110 j = 1, nrhs
531  t1 = b( k, j )
532  t2 = b( k+1, j )
533  b( k, j ) = d11*t1 + d12*t2
534  b( k+1, j ) = d21*t1 + d22*t2
535  110 continue
536  END IF
537  k = k + 2
538  END IF
539  go to 100
540  120 continue
541  END IF
542  END IF
543  return
544 *
545 * End of ZLAVSY
546 *
547  END