1*> \brief \b ZLAVSP
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 ZLAVSP( UPLO, TRANS, DIAG, N, NRHS, A, IPIV, B, LDB,
12*                          INFO )
13*
14*       .. Scalar Arguments ..
15*       CHARACTER          DIAG, TRANS, UPLO
16*       INTEGER            INFO, LDB, N, NRHS
17*       ..
18*       .. Array Arguments ..
19*       INTEGER            IPIV( * )
20*       COMPLEX*16         A( * ), B( LDB, * )
21*       ..
22*
23*
24*> \par Purpose:
25*  =============
26*>
27*> \verbatim
28*>
29*>    ZLAVSP  performs one of the matrix-vector operations
30*>       x := A*x  or  x := A^T*x,
31*>    where x is an N element vector and  A is one of the factors
32*>    from the symmetric factorization computed by ZSPTRF.
33*>    ZSPTRF produces a factorization of the form
34*>         U * D * U^T     or     L * D * L^T,
35*>    where U (or L) is a product of permutation and unit upper (lower)
36*>    triangular matrices, U^T (or L^T) is the transpose of
37*>    U (or L), and D is symmetric and block diagonal with 1 x 1 and
38*>    2 x 2 diagonal blocks.  The multipliers for the transformations
39*>    and the upper or lower triangular parts of the diagonal blocks
40*>    are stored columnwise in packed format in the linear array A.
41*>
42*>    If TRANS = 'N' or 'n', ZLAVSP multiplies either by U or U * D
43*>    (or L or L * D).
44*>    If TRANS = 'C' or 'c', ZLAVSP multiplies either by U^T or D * U^T
45*>    (or L^T or D * L^T ).
46*> \endverbatim
47*
48*  Arguments:
49*  ==========
50*
51*> \verbatim
52*>  UPLO   - CHARACTER*1
53*>           On entry, UPLO specifies whether the triangular matrix
54*>           stored in A is upper or lower triangular.
55*>              UPLO = 'U' or 'u'   The matrix is upper triangular.
56*>              UPLO = 'L' or 'l'   The matrix is lower triangular.
57*>           Unchanged on exit.
58*>
59*>  TRANS  - CHARACTER*1
60*>           On entry, TRANS specifies the operation to be performed as
61*>           follows:
62*>              TRANS = 'N' or 'n'   x := A*x.
63*>              TRANS = 'T' or 't'   x := A^T*x.
64*>           Unchanged on exit.
65*>
66*>  DIAG   - CHARACTER*1
67*>           On entry, DIAG specifies whether the diagonal blocks are
68*>           assumed to be unit matrices, as follows:
69*>              DIAG = 'U' or 'u'   Diagonal blocks are unit matrices.
70*>              DIAG = 'N' or 'n'   Diagonal blocks are non-unit.
71*>           Unchanged on exit.
72*>
73*>  N      - INTEGER
74*>           On entry, N specifies the order of the matrix A.
75*>           N must be at least zero.
76*>           Unchanged on exit.
77*>
78*>  NRHS   - INTEGER
79*>           On entry, NRHS specifies the number of right hand sides,
80*>           i.e., the number of vectors x to be multiplied by A.
81*>           NRHS must be at least zero.
82*>           Unchanged on exit.
83*>
84*>  A      - COMPLEX*16 array, dimension( N*(N+1)/2 )
85*>           On entry, A contains a block diagonal matrix and the
86*>           multipliers of the transformations used to obtain it,
87*>           stored as a packed triangular matrix.
88*>           Unchanged on exit.
89*>
90*>  IPIV   - INTEGER array, dimension( N )
91*>           On entry, IPIV contains the vector of pivot indices as
92*>           determined by ZSPTRF.
93*>           If IPIV( K ) = K, no interchange was done.
94*>           If IPIV( K ) <> K but IPIV( K ) > 0, then row K was inter-
95*>           changed with row IPIV( K ) and a 1 x 1 pivot block was used.
96*>           If IPIV( K ) < 0 and UPLO = 'U', then row K-1 was exchanged
97*>           with row | IPIV( K ) | and a 2 x 2 pivot block was used.
98*>           If IPIV( K ) < 0 and UPLO = 'L', then row K+1 was exchanged
99*>           with row | IPIV( K ) | and a 2 x 2 pivot block was used.
100*>
101*>  B      - COMPLEX*16 array, dimension( LDB, NRHS )
102*>           On entry, B contains NRHS vectors of length N.
103*>           On exit, B is overwritten with the product A * B.
104*>
105*>  LDB    - INTEGER
106*>           On entry, LDB contains the leading dimension of B as
107*>           declared in the calling program.  LDB must be at least
108*>           max( 1, N ).
109*>           Unchanged on exit.
110*>
111*>  INFO   - INTEGER
112*>           INFO is the error flag.
113*>           On exit, a value of 0 indicates a successful exit.
114*>           A negative value, say -K, indicates that the K-th argument
115*>           has an illegal value.
116*> \endverbatim
117*
118*  Authors:
119*  ========
120*
121*> \author Univ. of Tennessee
122*> \author Univ. of California Berkeley
123*> \author Univ. of Colorado Denver
124*> \author NAG Ltd.
125*
126*> \ingroup complex16_lin
127*
128*  =====================================================================
129      SUBROUTINE ZLAVSP( UPLO, TRANS, DIAG, N, NRHS, A, IPIV, B, LDB,
130     $                   INFO )
131*
132*  -- LAPACK test routine --
133*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
134*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
135*
136*     .. Scalar Arguments ..
137      CHARACTER          DIAG, TRANS, UPLO
138      INTEGER            INFO, LDB, N, NRHS
139*     ..
140*     .. Array Arguments ..
141      INTEGER            IPIV( * )
142      COMPLEX*16         A( * ), B( LDB, * )
143*     ..
144*
145*  =====================================================================
146*
147*     .. Parameters ..
148      COMPLEX*16         ONE
149      PARAMETER          ( ONE = ( 1.0D+0, 0.0D+0 ) )
150*     ..
151*     .. Local Scalars ..
152      LOGICAL            NOUNIT
153      INTEGER            J, K, KC, KCNEXT, KP
154      COMPLEX*16         D11, D12, D21, D22, T1, T2
155*     ..
156*     .. External Functions ..
157      LOGICAL            LSAME
158      EXTERNAL           LSAME
159*     ..
160*     .. External Subroutines ..
161      EXTERNAL           XERBLA, ZGEMV, ZGERU, ZSCAL, ZSWAP
162*     ..
163*     .. Intrinsic Functions ..
164      INTRINSIC          ABS, MAX
165*     ..
166*     .. Executable Statements ..
167*
168*     Test the input parameters.
169*
170      INFO = 0
171      IF( .NOT.LSAME( UPLO, 'U' ) .AND. .NOT.LSAME( UPLO, 'L' ) ) THEN
172         INFO = -1
173      ELSE IF( .NOT.LSAME( TRANS, 'N' ) .AND. .NOT.LSAME( TRANS, 'T' ) )
174     $          THEN
175         INFO = -2
176      ELSE IF( .NOT.LSAME( DIAG, 'U' ) .AND. .NOT.LSAME( DIAG, 'N' ) )
177     $          THEN
178         INFO = -3
179      ELSE IF( N.LT.0 ) THEN
180         INFO = -4
181      ELSE IF( LDB.LT.MAX( 1, N ) ) THEN
182         INFO = -8
183      END IF
184      IF( INFO.NE.0 ) THEN
185         CALL XERBLA( 'ZLAVSP ', -INFO )
186         RETURN
187      END IF
188*
189*     Quick return if possible.
190*
191      IF( N.EQ.0 )
192     $   RETURN
193*
194      NOUNIT = LSAME( DIAG, 'N' )
195*------------------------------------------
196*
197*     Compute  B := A * B  (No transpose)
198*
199*------------------------------------------
200      IF( LSAME( TRANS, 'N' ) ) THEN
201*
202*        Compute  B := U*B
203*        where U = P(m)*inv(U(m))* ... *P(1)*inv(U(1))
204*
205         IF( LSAME( UPLO, 'U' ) ) THEN
206*
207*        Loop forward applying the transformations.
208*
209            K = 1
210            KC = 1
211   10       CONTINUE
212            IF( K.GT.N )
213     $         GO TO 30
214*
215*           1 x 1 pivot block
216*
217            IF( IPIV( K ).GT.0 ) THEN
218*
219*              Multiply by the diagonal element if forming U * D.
220*
221               IF( NOUNIT )
222     $            CALL ZSCAL( NRHS, A( KC+K-1 ), B( K, 1 ), LDB )
223*
224*              Multiply by P(K) * inv(U(K))  if K > 1.
225*
226               IF( K.GT.1 ) THEN
227*
228*                 Apply the transformation.
229*
230                  CALL ZGERU( K-1, NRHS, ONE, A( KC ), 1, B( K, 1 ),
231     $                        LDB, B( 1, 1 ), LDB )
232*
233*                 Interchange if P(K) != I.
234*
235                  KP = IPIV( K )
236                  IF( KP.NE.K )
237     $               CALL ZSWAP( NRHS, B( K, 1 ), LDB, B( KP, 1 ), LDB )
238               END IF
239               KC = KC + K
240               K = K + 1
241            ELSE
242*
243*              2 x 2 pivot block
244*
245               KCNEXT = KC + K
246*
247*              Multiply by the diagonal block if forming U * D.
248*
249               IF( NOUNIT ) THEN
250                  D11 = A( KCNEXT-1 )
251                  D22 = A( KCNEXT+K )
252                  D12 = A( KCNEXT+K-1 )
253                  D21 = D12
254                  DO 20 J = 1, NRHS
255                     T1 = B( K, J )
256                     T2 = B( K+1, J )
257                     B( K, J ) = D11*T1 + D12*T2
258                     B( K+1, J ) = D21*T1 + D22*T2
259   20             CONTINUE
260               END IF
261*
262*              Multiply by  P(K) * inv(U(K))  if K > 1.
263*
264               IF( K.GT.1 ) THEN
265*
266*                 Apply the transformations.
267*
268                  CALL ZGERU( K-1, NRHS, ONE, A( KC ), 1, B( K, 1 ),
269     $                        LDB, B( 1, 1 ), LDB )
270                  CALL ZGERU( K-1, NRHS, ONE, A( KCNEXT ), 1,
271     $                        B( K+1, 1 ), LDB, B( 1, 1 ), LDB )
272*
273*                 Interchange if P(K) != I.
274*
275                  KP = ABS( IPIV( K ) )
276                  IF( KP.NE.K )
277     $               CALL ZSWAP( NRHS, B( K, 1 ), LDB, B( KP, 1 ), LDB )
278               END IF
279               KC = KCNEXT + K + 1
280               K = K + 2
281            END IF
282            GO TO 10
283   30       CONTINUE
284*
285*        Compute  B := L*B
286*        where L = P(1)*inv(L(1))* ... *P(m)*inv(L(m)) .
287*
288         ELSE
289*
290*           Loop backward applying the transformations to B.
291*
292            K = N
293            KC = N*( N+1 ) / 2 + 1
294   40       CONTINUE
295            IF( K.LT.1 )
296     $         GO TO 60
297            KC = KC - ( N-K+1 )
298*
299*           Test the pivot index.  If greater than zero, a 1 x 1
300*           pivot was used, otherwise a 2 x 2 pivot was used.
301*
302            IF( IPIV( K ).GT.0 ) THEN
303*
304*              1 x 1 pivot block:
305*
306*              Multiply by the diagonal element if forming L * D.
307*
308               IF( NOUNIT )
309     $            CALL ZSCAL( NRHS, A( KC ), B( K, 1 ), LDB )
310*
311*              Multiply by  P(K) * inv(L(K))  if K < N.
312*
313               IF( K.NE.N ) THEN
314                  KP = IPIV( K )
315*
316*                 Apply the transformation.
317*
318                  CALL ZGERU( N-K, NRHS, ONE, A( KC+1 ), 1, B( K, 1 ),
319     $                        LDB, B( K+1, 1 ), LDB )
320*
321*                 Interchange if a permutation was applied at the
322*                 K-th step of the factorization.
323*
324                  IF( KP.NE.K )
325     $               CALL ZSWAP( NRHS, B( K, 1 ), LDB, B( KP, 1 ), LDB )
326               END IF
327               K = K - 1
328*
329            ELSE
330*
331*              2 x 2 pivot block:
332*
333               KCNEXT = KC - ( N-K+2 )
334*
335*              Multiply by the diagonal block if forming L * D.
336*
337               IF( NOUNIT ) THEN
338                  D11 = A( KCNEXT )
339                  D22 = A( KC )
340                  D21 = A( KCNEXT+1 )
341                  D12 = D21
342                  DO 50 J = 1, NRHS
343                     T1 = B( K-1, J )
344                     T2 = B( K, J )
345                     B( K-1, J ) = D11*T1 + D12*T2
346                     B( K, J ) = D21*T1 + D22*T2
347   50             CONTINUE
348               END IF
349*
350*              Multiply by  P(K) * inv(L(K))  if K < N.
351*
352               IF( K.NE.N ) THEN
353*
354*                 Apply the transformation.
355*
356                  CALL ZGERU( N-K, NRHS, ONE, A( KC+1 ), 1, B( K, 1 ),
357     $                        LDB, B( K+1, 1 ), LDB )
358                  CALL ZGERU( N-K, NRHS, ONE, A( KCNEXT+2 ), 1,
359     $                        B( K-1, 1 ), LDB, B( K+1, 1 ), LDB )
360*
361*                 Interchange if a permutation was applied at the
362*                 K-th step of the factorization.
363*
364                  KP = ABS( IPIV( K ) )
365                  IF( KP.NE.K )
366     $               CALL ZSWAP( NRHS, B( K, 1 ), LDB, B( KP, 1 ), LDB )
367               END IF
368               KC = KCNEXT
369               K = K - 2
370            END IF
371            GO TO 40
372   60       CONTINUE
373         END IF
374*-------------------------------------------------
375*
376*     Compute  B := A^T * B  (transpose)
377*
378*-------------------------------------------------
379      ELSE
380*
381*        Form  B := U^T*B
382*        where U  = P(m)*inv(U(m))* ... *P(1)*inv(U(1))
383*        and   U^T = inv(U^T(1))*P(1)* ... *inv(U^T(m))*P(m)
384*
385         IF( LSAME( UPLO, 'U' ) ) THEN
386*
387*           Loop backward applying the transformations.
388*
389            K = N
390            KC = N*( N+1 ) / 2 + 1
391   70       CONTINUE
392            IF( K.LT.1 )
393     $         GO TO 90
394            KC = KC - K
395*
396*           1 x 1 pivot block.
397*
398            IF( IPIV( K ).GT.0 ) THEN
399               IF( K.GT.1 ) THEN
400*
401*                 Interchange if P(K) != I.
402*
403                  KP = IPIV( K )
404                  IF( KP.NE.K )
405     $               CALL ZSWAP( NRHS, B( K, 1 ), LDB, B( KP, 1 ), LDB )
406*
407*                 Apply the transformation:
408*                    y := y - B' * conjg(x)
409*                 where x is a column of A and y is a row of B.
410*
411                  CALL ZGEMV( 'Transpose', K-1, NRHS, ONE, B, LDB,
412     $                        A( KC ), 1, ONE, B( K, 1 ), LDB )
413               END IF
414               IF( NOUNIT )
415     $            CALL ZSCAL( NRHS, A( KC+K-1 ), B( K, 1 ), LDB )
416               K = K - 1
417*
418*           2 x 2 pivot block.
419*
420            ELSE
421               KCNEXT = KC - ( K-1 )
422               IF( K.GT.2 ) THEN
423*
424*                 Interchange if P(K) != I.
425*
426                  KP = ABS( IPIV( K ) )
427                  IF( KP.NE.K-1 )
428     $               CALL ZSWAP( NRHS, B( K-1, 1 ), LDB, B( KP, 1 ),
429     $                           LDB )
430*
431*                 Apply the transformations.
432*
433                  CALL ZGEMV( 'Transpose', K-2, NRHS, ONE, B, LDB,
434     $                        A( KC ), 1, ONE, B( K, 1 ), LDB )
435*
436                  CALL ZGEMV( 'Transpose', K-2, NRHS, ONE, B, LDB,
437     $                        A( KCNEXT ), 1, ONE, B( K-1, 1 ), LDB )
438               END IF
439*
440*              Multiply by the diagonal block if non-unit.
441*
442               IF( NOUNIT ) THEN
443                  D11 = A( KC-1 )
444                  D22 = A( KC+K-1 )
445                  D12 = A( KC+K-2 )
446                  D21 = D12
447                  DO 80 J = 1, NRHS
448                     T1 = B( K-1, J )
449                     T2 = B( K, J )
450                     B( K-1, J ) = D11*T1 + D12*T2
451                     B( K, J ) = D21*T1 + D22*T2
452   80             CONTINUE
453               END IF
454               KC = KCNEXT
455               K = K - 2
456            END IF
457            GO TO 70
458   90       CONTINUE
459*
460*        Form  B := L^T*B
461*        where L  = P(1)*inv(L(1))* ... *P(m)*inv(L(m))
462*        and   L^T = inv(L(m))*P(m)* ... *inv(L(1))*P(1)
463*
464         ELSE
465*
466*           Loop forward applying the L-transformations.
467*
468            K = 1
469            KC = 1
470  100       CONTINUE
471            IF( K.GT.N )
472     $         GO TO 120
473*
474*           1 x 1 pivot block
475*
476            IF( IPIV( K ).GT.0 ) THEN
477               IF( K.LT.N ) THEN
478*
479*                 Interchange if P(K) != I.
480*
481                  KP = IPIV( K )
482                  IF( KP.NE.K )
483     $               CALL ZSWAP( NRHS, B( K, 1 ), LDB, B( KP, 1 ), LDB )
484*
485*                 Apply the transformation
486*
487                  CALL ZGEMV( 'Transpose', N-K, NRHS, ONE, B( K+1, 1 ),
488     $                        LDB, A( KC+1 ), 1, ONE, B( K, 1 ), LDB )
489               END IF
490               IF( NOUNIT )
491     $            CALL ZSCAL( NRHS, A( KC ), B( K, 1 ), LDB )
492               KC = KC + N - K + 1
493               K = K + 1
494*
495*           2 x 2 pivot block.
496*
497            ELSE
498               KCNEXT = KC + N - K + 1
499               IF( K.LT.N-1 ) THEN
500*
501*              Interchange if P(K) != I.
502*
503                  KP = ABS( IPIV( K ) )
504                  IF( KP.NE.K+1 )
505     $               CALL ZSWAP( NRHS, B( K+1, 1 ), LDB, B( KP, 1 ),
506     $                           LDB )
507*
508*                 Apply the transformation
509*
510                  CALL ZGEMV( 'Transpose', N-K-1, NRHS, ONE,
511     $                        B( K+2, 1 ), LDB, A( KCNEXT+1 ), 1, ONE,
512     $                        B( K+1, 1 ), LDB )
513*
514                  CALL ZGEMV( 'Transpose', N-K-1, NRHS, ONE,
515     $                        B( K+2, 1 ), LDB, A( KC+2 ), 1, ONE,
516     $                        B( K, 1 ), LDB )
517               END IF
518*
519*              Multiply by the diagonal block if non-unit.
520*
521               IF( NOUNIT ) THEN
522                  D11 = A( KC )
523                  D22 = A( KCNEXT )
524                  D21 = A( KC+1 )
525                  D12 = D21
526                  DO 110 J = 1, NRHS
527                     T1 = B( K, J )
528                     T2 = B( K+1, J )
529                     B( K, J ) = D11*T1 + D12*T2
530                     B( K+1, J ) = D21*T1 + D22*T2
531  110             CONTINUE
532               END IF
533               KC = KCNEXT + ( N-K )
534               K = K + 2
535            END IF
536            GO TO 100
537  120       CONTINUE
538         END IF
539*
540      END IF
541      RETURN
542*
543*     End of ZLAVSP
544*
545      END
546