1*> \brief \b ZSYMV computes a matrix-vector product for a complex symmetric matrix.
2*
3*  =========== DOCUMENTATION ===========
4*
5* Online html documentation available at
6*            http://www.netlib.org/lapack/explore-html/
7*
8*> \htmlonly
9*> Download ZSYMV + dependencies
10*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.tgz?format=tgz&filename=/lapack/lapack_routine/zsymv.f">
11*> [TGZ]</a>
12*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.zip?format=zip&filename=/lapack/lapack_routine/zsymv.f">
13*> [ZIP]</a>
14*> <a href="http://www.netlib.org/cgi-bin/netlibfiles.txt?format=txt&filename=/lapack/lapack_routine/zsymv.f">
15*> [TXT]</a>
16*> \endhtmlonly
17*
18*  Definition:
19*  ===========
20*
21*       SUBROUTINE ZSYMV( UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY )
22*
23*       .. Scalar Arguments ..
24*       CHARACTER          UPLO
25*       INTEGER            INCX, INCY, LDA, N
26*       COMPLEX*16         ALPHA, BETA
27*       ..
28*       .. Array Arguments ..
29*       COMPLEX*16         A( LDA, * ), X( * ), Y( * )
30*       ..
31*
32*
33*> \par Purpose:
34*  =============
35*>
36*> \verbatim
37*>
38*> ZSYMV  performs the matrix-vector  operation
39*>
40*>    y := alpha*A*x + beta*y,
41*>
42*> where alpha and beta are scalars, x and y are n element vectors and
43*> A is an n by n symmetric matrix.
44*> \endverbatim
45*
46*  Arguments:
47*  ==========
48*
49*> \param[in] UPLO
50*> \verbatim
51*>          UPLO is CHARACTER*1
52*>           On entry, UPLO specifies whether the upper or lower
53*>           triangular part of the array A is to be referenced as
54*>           follows:
55*>
56*>              UPLO = 'U' or 'u'   Only the upper triangular part of A
57*>                                  is to be referenced.
58*>
59*>              UPLO = 'L' or 'l'   Only the lower triangular part of A
60*>                                  is to be referenced.
61*>
62*>           Unchanged on exit.
63*> \endverbatim
64*>
65*> \param[in] N
66*> \verbatim
67*>          N is INTEGER
68*>           On entry, N specifies the order of the matrix A.
69*>           N must be at least zero.
70*>           Unchanged on exit.
71*> \endverbatim
72*>
73*> \param[in] ALPHA
74*> \verbatim
75*>          ALPHA is COMPLEX*16
76*>           On entry, ALPHA specifies the scalar alpha.
77*>           Unchanged on exit.
78*> \endverbatim
79*>
80*> \param[in] A
81*> \verbatim
82*>          A is COMPLEX*16 array, dimension ( LDA, N )
83*>           Before entry, with  UPLO = 'U' or 'u', the leading n by n
84*>           upper triangular part of the array A must contain the upper
85*>           triangular part of the symmetric matrix and the strictly
86*>           lower triangular part of A is not referenced.
87*>           Before entry, with UPLO = 'L' or 'l', the leading n by n
88*>           lower triangular part of the array A must contain the lower
89*>           triangular part of the symmetric matrix and the strictly
90*>           upper triangular part of A is not referenced.
91*>           Unchanged on exit.
92*> \endverbatim
93*>
94*> \param[in] LDA
95*> \verbatim
96*>          LDA is INTEGER
97*>           On entry, LDA specifies the first dimension of A as declared
98*>           in the calling (sub) program. LDA must be at least
99*>           max( 1, N ).
100*>           Unchanged on exit.
101*> \endverbatim
102*>
103*> \param[in] X
104*> \verbatim
105*>          X is COMPLEX*16 array, dimension at least
106*>           ( 1 + ( N - 1 )*abs( INCX ) ).
107*>           Before entry, the incremented array X must contain the N-
108*>           element vector x.
109*>           Unchanged on exit.
110*> \endverbatim
111*>
112*> \param[in] INCX
113*> \verbatim
114*>          INCX is INTEGER
115*>           On entry, INCX specifies the increment for the elements of
116*>           X. INCX must not be zero.
117*>           Unchanged on exit.
118*> \endverbatim
119*>
120*> \param[in] BETA
121*> \verbatim
122*>          BETA is COMPLEX*16
123*>           On entry, BETA specifies the scalar beta. When BETA is
124*>           supplied as zero then Y need not be set on input.
125*>           Unchanged on exit.
126*> \endverbatim
127*>
128*> \param[in,out] Y
129*> \verbatim
130*>          Y is COMPLEX*16 array, dimension at least
131*>           ( 1 + ( N - 1 )*abs( INCY ) ).
132*>           Before entry, the incremented array Y must contain the n
133*>           element vector y. On exit, Y is overwritten by the updated
134*>           vector y.
135*> \endverbatim
136*>
137*> \param[in] INCY
138*> \verbatim
139*>          INCY is INTEGER
140*>           On entry, INCY specifies the increment for the elements of
141*>           Y. INCY must not be zero.
142*>           Unchanged on exit.
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*> \ingroup complex16SYauxiliary
154*
155*  =====================================================================
156      SUBROUTINE ZSYMV( UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY )
157*
158*  -- LAPACK auxiliary routine --
159*  -- LAPACK is a software package provided by Univ. of Tennessee,    --
160*  -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
161*
162*     .. Scalar Arguments ..
163      CHARACTER          UPLO
164      INTEGER            INCX, INCY, LDA, N
165      COMPLEX*16         ALPHA, BETA
166*     ..
167*     .. Array Arguments ..
168      COMPLEX*16         A( LDA, * ), X( * ), Y( * )
169*     ..
170*
171* =====================================================================
172*
173*     .. Parameters ..
174      COMPLEX*16         ONE
175      PARAMETER          ( ONE = ( 1.0D+0, 0.0D+0 ) )
176      COMPLEX*16         ZERO
177      PARAMETER          ( ZERO = ( 0.0D+0, 0.0D+0 ) )
178*     ..
179*     .. Local Scalars ..
180      INTEGER            I, INFO, IX, IY, J, JX, JY, KX, KY
181      COMPLEX*16         TEMP1, TEMP2
182*     ..
183*     .. External Functions ..
184      LOGICAL            LSAME
185      EXTERNAL           LSAME
186*     ..
187*     .. External Subroutines ..
188      EXTERNAL           XERBLA
189*     ..
190*     .. Intrinsic Functions ..
191      INTRINSIC          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( N.LT.0 ) THEN
201         INFO = 2
202      ELSE IF( LDA.LT.MAX( 1, N ) ) THEN
203         INFO = 5
204      ELSE IF( INCX.EQ.0 ) THEN
205         INFO = 7
206      ELSE IF( INCY.EQ.0 ) THEN
207         INFO = 10
208      END IF
209      IF( INFO.NE.0 ) THEN
210         CALL XERBLA( 'ZSYMV ', INFO )
211         RETURN
212      END IF
213*
214*     Quick return if possible.
215*
216      IF( ( N.EQ.0 ) .OR. ( ( ALPHA.EQ.ZERO ) .AND. ( BETA.EQ.ONE ) ) )
217     $   RETURN
218*
219*     Set up the start points in  X  and  Y.
220*
221      IF( INCX.GT.0 ) THEN
222         KX = 1
223      ELSE
224         KX = 1 - ( N-1 )*INCX
225      END IF
226      IF( INCY.GT.0 ) THEN
227         KY = 1
228      ELSE
229         KY = 1 - ( N-1 )*INCY
230      END IF
231*
232*     Start the operations. In this version the elements of A are
233*     accessed sequentially with one pass through the triangular part
234*     of A.
235*
236*     First form  y := beta*y.
237*
238      IF( BETA.NE.ONE ) THEN
239         IF( INCY.EQ.1 ) THEN
240            IF( BETA.EQ.ZERO ) THEN
241               DO 10 I = 1, N
242                  Y( I ) = ZERO
243   10          CONTINUE
244            ELSE
245               DO 20 I = 1, N
246                  Y( I ) = BETA*Y( I )
247   20          CONTINUE
248            END IF
249         ELSE
250            IY = KY
251            IF( BETA.EQ.ZERO ) THEN
252               DO 30 I = 1, N
253                  Y( IY ) = ZERO
254                  IY = IY + INCY
255   30          CONTINUE
256            ELSE
257               DO 40 I = 1, N
258                  Y( IY ) = BETA*Y( IY )
259                  IY = IY + INCY
260   40          CONTINUE
261            END IF
262         END IF
263      END IF
264      IF( ALPHA.EQ.ZERO )
265     $   RETURN
266      IF( LSAME( UPLO, 'U' ) ) THEN
267*
268*        Form  y  when A is stored in upper triangle.
269*
270         IF( ( INCX.EQ.1 ) .AND. ( INCY.EQ.1 ) ) THEN
271            DO 60 J = 1, N
272               TEMP1 = ALPHA*X( J )
273               TEMP2 = ZERO
274               DO 50 I = 1, J - 1
275                  Y( I ) = Y( I ) + TEMP1*A( I, J )
276                  TEMP2 = TEMP2 + A( I, J )*X( I )
277   50          CONTINUE
278               Y( J ) = Y( J ) + TEMP1*A( J, J ) + ALPHA*TEMP2
279   60       CONTINUE
280         ELSE
281            JX = KX
282            JY = KY
283            DO 80 J = 1, N
284               TEMP1 = ALPHA*X( JX )
285               TEMP2 = ZERO
286               IX = KX
287               IY = KY
288               DO 70 I = 1, J - 1
289                  Y( IY ) = Y( IY ) + TEMP1*A( I, J )
290                  TEMP2 = TEMP2 + A( I, J )*X( IX )
291                  IX = IX + INCX
292                  IY = IY + INCY
293   70          CONTINUE
294               Y( JY ) = Y( JY ) + TEMP1*A( J, J ) + ALPHA*TEMP2
295               JX = JX + INCX
296               JY = JY + INCY
297   80       CONTINUE
298         END IF
299      ELSE
300*
301*        Form  y  when A is stored in lower triangle.
302*
303         IF( ( INCX.EQ.1 ) .AND. ( INCY.EQ.1 ) ) THEN
304            DO 100 J = 1, N
305               TEMP1 = ALPHA*X( J )
306               TEMP2 = ZERO
307               Y( J ) = Y( J ) + TEMP1*A( J, J )
308               DO 90 I = J + 1, N
309                  Y( I ) = Y( I ) + TEMP1*A( I, J )
310                  TEMP2 = TEMP2 + A( I, J )*X( I )
311   90          CONTINUE
312               Y( J ) = Y( J ) + ALPHA*TEMP2
313  100       CONTINUE
314         ELSE
315            JX = KX
316            JY = KY
317            DO 120 J = 1, N
318               TEMP1 = ALPHA*X( JX )
319               TEMP2 = ZERO
320               Y( JY ) = Y( JY ) + TEMP1*A( J, J )
321               IX = JX
322               IY = JY
323               DO 110 I = J + 1, N
324                  IX = IX + INCX
325                  IY = IY + INCY
326                  Y( IY ) = Y( IY ) + TEMP1*A( I, J )
327                  TEMP2 = TEMP2 + A( I, J )*X( IX )
328  110          CONTINUE
329               Y( JY ) = Y( JY ) + ALPHA*TEMP2
330               JX = JX + INCX
331               JY = JY + INCY
332  120       CONTINUE
333         END IF
334      END IF
335*
336      RETURN
337*
338*     End of ZSYMV
339*
340      END
341