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

DSYMV

Purpose:
 DSYMV  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.
[in]N
          N is INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
[in]ALPHA
          ALPHA is DOUBLE PRECISION.
           On entry, ALPHA specifies the scalar alpha.
[in]A
          A is DOUBLE PRECISION array of 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.
[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 ).
[in]X
          X is DOUBLE PRECISION array of dimension at least
           ( 1 + ( n - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the n
           element vector x.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
[in]BETA
          BETA is DOUBLE PRECISION.
           On entry, BETA specifies the scalar beta. When BETA is
           supplied as zero then Y need not be set on input.
[in,out]Y
          Y is DOUBLE PRECISION array of 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.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Date
November 2011
Further Details:
  Level 2 Blas routine.
  The vector and matrix arguments are not referenced when N = 0, or M = 0

  -- Written on 22-October-1986.
     Jack Dongarra, Argonne National Lab.
     Jeremy Du Croz, Nag Central Office.
     Sven Hammarling, Nag Central Office.
     Richard Hanson, Sandia National Labs.

Definition at line 154 of file dsymv.f.

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