LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
zsymv.f
Go to the documentation of this file.
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 *> \date September 2012
154 *
155 *> \ingroup complex16SYauxiliary
156 *
157 * =====================================================================
158  SUBROUTINE zsymv( UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY )
159 *
160 * -- LAPACK auxiliary routine (version 3.4.2) --
161 * -- LAPACK is a software package provided by Univ. of Tennessee, --
162 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
163 * September 2012
164 *
165 * .. Scalar Arguments ..
166  CHARACTER uplo
167  INTEGER incx, incy, lda, n
168  COMPLEX*16 alpha, beta
169 * ..
170 * .. Array Arguments ..
171  COMPLEX*16 a( lda, * ), x( * ), y( * )
172 * ..
173 *
174 * =====================================================================
175 *
176 * .. Parameters ..
177  COMPLEX*16 one
178  parameter( one = ( 1.0d+0, 0.0d+0 ) )
179  COMPLEX*16 zero
180  parameter( zero = ( 0.0d+0, 0.0d+0 ) )
181 * ..
182 * .. Local Scalars ..
183  INTEGER i, info, ix, iy, j, jx, jy, kx, ky
184  COMPLEX*16 temp1, temp2
185 * ..
186 * .. External Functions ..
187  LOGICAL lsame
188  EXTERNAL lsame
189 * ..
190 * .. External Subroutines ..
191  EXTERNAL xerbla
192 * ..
193 * .. Intrinsic Functions ..
194  INTRINSIC max
195 * ..
196 * .. Executable Statements ..
197 *
198 * Test the input parameters.
199 *
200  info = 0
201  IF( .NOT.lsame( uplo, 'U' ) .AND. .NOT.lsame( uplo, 'L' ) ) THEN
202  info = 1
203  ELSE IF( n.LT.0 ) THEN
204  info = 2
205  ELSE IF( lda.LT.max( 1, n ) ) THEN
206  info = 5
207  ELSE IF( incx.EQ.0 ) THEN
208  info = 7
209  ELSE IF( incy.EQ.0 ) THEN
210  info = 10
211  END IF
212  IF( info.NE.0 ) THEN
213  CALL xerbla( 'ZSYMV ', info )
214  return
215  END IF
216 *
217 * Quick return if possible.
218 *
219  IF( ( n.EQ.0 ) .OR. ( ( alpha.EQ.zero ) .AND. ( beta.EQ.one ) ) )
220  $ return
221 *
222 * Set up the start points in X and Y.
223 *
224  IF( incx.GT.0 ) THEN
225  kx = 1
226  ELSE
227  kx = 1 - ( n-1 )*incx
228  END IF
229  IF( incy.GT.0 ) THEN
230  ky = 1
231  ELSE
232  ky = 1 - ( n-1 )*incy
233  END IF
234 *
235 * Start the operations. In this version the elements of A are
236 * accessed sequentially with one pass through the triangular part
237 * of A.
238 *
239 * First form y := beta*y.
240 *
241  IF( beta.NE.one ) THEN
242  IF( incy.EQ.1 ) THEN
243  IF( beta.EQ.zero ) THEN
244  DO 10 i = 1, n
245  y( i ) = zero
246  10 continue
247  ELSE
248  DO 20 i = 1, n
249  y( i ) = beta*y( i )
250  20 continue
251  END IF
252  ELSE
253  iy = ky
254  IF( beta.EQ.zero ) THEN
255  DO 30 i = 1, n
256  y( iy ) = zero
257  iy = iy + incy
258  30 continue
259  ELSE
260  DO 40 i = 1, n
261  y( iy ) = beta*y( iy )
262  iy = iy + incy
263  40 continue
264  END IF
265  END IF
266  END IF
267  IF( alpha.EQ.zero )
268  $ return
269  IF( lsame( uplo, 'U' ) ) THEN
270 *
271 * Form y when A is stored in upper triangle.
272 *
273  IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
274  DO 60 j = 1, n
275  temp1 = alpha*x( j )
276  temp2 = zero
277  DO 50 i = 1, j - 1
278  y( i ) = y( i ) + temp1*a( i, j )
279  temp2 = temp2 + a( i, j )*x( i )
280  50 continue
281  y( j ) = y( j ) + temp1*a( j, j ) + alpha*temp2
282  60 continue
283  ELSE
284  jx = kx
285  jy = ky
286  DO 80 j = 1, n
287  temp1 = alpha*x( jx )
288  temp2 = zero
289  ix = kx
290  iy = ky
291  DO 70 i = 1, j - 1
292  y( iy ) = y( iy ) + temp1*a( i, j )
293  temp2 = temp2 + a( i, j )*x( ix )
294  ix = ix + incx
295  iy = iy + incy
296  70 continue
297  y( jy ) = y( jy ) + temp1*a( j, j ) + alpha*temp2
298  jx = jx + incx
299  jy = jy + incy
300  80 continue
301  END IF
302  ELSE
303 *
304 * Form y when A is stored in lower triangle.
305 *
306  IF( ( incx.EQ.1 ) .AND. ( incy.EQ.1 ) ) THEN
307  DO 100 j = 1, n
308  temp1 = alpha*x( j )
309  temp2 = zero
310  y( j ) = y( j ) + temp1*a( j, j )
311  DO 90 i = j + 1, n
312  y( i ) = y( i ) + temp1*a( i, j )
313  temp2 = temp2 + a( i, j )*x( i )
314  90 continue
315  y( j ) = y( j ) + alpha*temp2
316  100 continue
317  ELSE
318  jx = kx
319  jy = ky
320  DO 120 j = 1, n
321  temp1 = alpha*x( jx )
322  temp2 = zero
323  y( jy ) = y( jy ) + temp1*a( j, j )
324  ix = jx
325  iy = jy
326  DO 110 i = j + 1, n
327  ix = ix + incx
328  iy = iy + incy
329  y( iy ) = y( iy ) + temp1*a( i, j )
330  temp2 = temp2 + a( i, j )*x( ix )
331  110 continue
332  y( jy ) = y( jy ) + alpha*temp2
333  jx = jx + incx
334  jy = jy + incy
335  120 continue
336  END IF
337  END IF
338 *
339  return
340 *
341 * End of ZSYMV
342 *
343  END