LAPACK 3.12.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ dsymv()

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, 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, 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, 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.
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 151 of file dsymv.f.

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