LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine zsymv ( character  UPLO,
integer  N,
complex*16  ALPHA,
complex*16, dimension( lda, * )  A,
integer  LDA,
complex*16, dimension( * )  X,
integer  INCX,
complex*16  BETA,
complex*16, dimension( * )  Y,
integer  INCY 
)

ZSYMV computes a matrix-vector product for a complex symmetric matrix.

Download ZSYMV + dependencies [TGZ] [ZIP] [TXT]

Purpose:
 ZSYMV  performs the matrix-vector  operation

    y := alpha*A*x + beta*y,

 where alpha and beta are scalars, x and y are n element vectors and
 A is an n by n symmetric matrix.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the upper or lower
           triangular part of the array A is to be referenced as
           follows:

              UPLO = 'U' or 'u'   Only the upper triangular part of A
                                  is to be referenced.

              UPLO = 'L' or 'l'   Only the lower triangular part of A
                                  is to be referenced.

           Unchanged on exit.
[in]N
          N is INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
           Unchanged on exit.
[in]ALPHA
          ALPHA is COMPLEX*16
           On entry, ALPHA specifies the scalar alpha.
           Unchanged on exit.
[in]A
          A is COMPLEX*16 array, dimension ( LDA, N )
           Before entry, with  UPLO = 'U' or 'u', the leading n by n
           upper triangular part of the array A must contain the upper
           triangular part of the symmetric matrix and the strictly
           lower triangular part of A is not referenced.
           Before entry, with UPLO = 'L' or 'l', the leading n by n
           lower triangular part of the array A must contain the lower
           triangular part of the symmetric matrix and the strictly
           upper triangular part of A is not referenced.
           Unchanged on exit.
[in]LDA
          LDA is INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in the calling (sub) program. LDA must be at least
           max( 1, N ).
           Unchanged on exit.
[in]X
          X is COMPLEX*16 array, dimension at least
           ( 1 + ( N - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the N-
           element vector x.
           Unchanged on exit.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
           Unchanged on exit.
[in]BETA
          BETA is COMPLEX*16
           On entry, BETA specifies the scalar beta. When BETA is
           supplied as zero then Y need not be set on input.
           Unchanged on exit.
[in,out]Y
          Y is COMPLEX*16 array, dimension at least
           ( 1 + ( N - 1 )*abs( INCY ) ).
           Before entry, the incremented array Y must contain the n
           element vector y. On exit, Y is overwritten by the updated
           vector y.
[in]INCY
          INCY is INTEGER
           On entry, INCY specifies the increment for the elements of
           Y. INCY must not be zero.
           Unchanged on exit.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
September 2012

Definition at line 159 of file zsymv.f.

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 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function:

Here is the caller graph for this function: