LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
ssymv.f
Go to the documentation of this file.
1 *> \brief \b SSYMV
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE SSYMV(UPLO,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
12 *
13 * .. Scalar Arguments ..
14 * REAL ALPHA,BETA
15 * INTEGER INCX,INCY,LDA,N
16 * CHARACTER UPLO
17 * ..
18 * .. Array Arguments ..
19 * REAL A(LDA,*),X(*),Y(*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> SSYMV performs the matrix-vector operation
29 *>
30 *> y := alpha*A*x + beta*y,
31 *>
32 *> where alpha and beta are scalars, x and y are n element vectors and
33 *> A is an n by n symmetric matrix.
34 *> \endverbatim
35 *
36 * Arguments:
37 * ==========
38 *
39 *> \param[in] UPLO
40 *> \verbatim
41 *> UPLO is CHARACTER*1
42 *> On entry, UPLO specifies whether the upper or lower
43 *> triangular part of the array A is to be referenced as
44 *> follows:
45 *>
46 *> UPLO = 'U' or 'u' Only the upper triangular part of A
47 *> is to be referenced.
48 *>
49 *> UPLO = 'L' or 'l' Only the lower triangular part of A
50 *> is to be referenced.
51 *> \endverbatim
52 *>
53 *> \param[in] N
54 *> \verbatim
55 *> N is INTEGER
56 *> On entry, N specifies the order of the matrix A.
57 *> N must be at least zero.
58 *> \endverbatim
59 *>
60 *> \param[in] ALPHA
61 *> \verbatim
62 *> ALPHA is REAL
63 *> On entry, ALPHA specifies the scalar alpha.
64 *> \endverbatim
65 *>
66 *> \param[in] A
67 *> \verbatim
68 *> A is REAL array of DIMENSION ( LDA, n ).
69 *> Before entry with UPLO = 'U' or 'u', the leading n by n
70 *> upper triangular part of the array A must contain the upper
71 *> triangular part of the symmetric matrix and the strictly
72 *> lower triangular part of A is not referenced.
73 *> Before entry with UPLO = 'L' or 'l', the leading n by n
74 *> lower triangular part of the array A must contain the lower
75 *> triangular part of the symmetric matrix and the strictly
76 *> upper triangular part of A is not referenced.
77 *> \endverbatim
78 *>
79 *> \param[in] LDA
80 *> \verbatim
81 *> LDA is INTEGER
82 *> On entry, LDA specifies the first dimension of A as declared
83 *> in the calling (sub) program. LDA must be at least
84 *> max( 1, n ).
85 *> \endverbatim
86 *>
87 *> \param[in] X
88 *> \verbatim
89 *> X is REAL array of dimension at least
90 *> ( 1 + ( n - 1 )*abs( INCX ) ).
91 *> Before entry, the incremented array X must contain the n
92 *> element vector x.
93 *> \endverbatim
94 *>
95 *> \param[in] INCX
96 *> \verbatim
97 *> INCX is INTEGER
98 *> On entry, INCX specifies the increment for the elements of
99 *> X. INCX must not be zero.
100 *> \endverbatim
101 *>
102 *> \param[in] BETA
103 *> \verbatim
104 *> BETA is REAL
105 *> On entry, BETA specifies the scalar beta. When BETA is
106 *> supplied as zero then Y need not be set on input.
107 *> \endverbatim
108 *>
109 *> \param[in,out] Y
110 *> \verbatim
111 *> Y is REAL array of dimension at least
112 *> ( 1 + ( n - 1 )*abs( INCY ) ).
113 *> Before entry, the incremented array Y must contain the n
114 *> element vector y. On exit, Y is overwritten by the updated
115 *> vector y.
116 *> \endverbatim
117 *>
118 *> \param[in] INCY
119 *> \verbatim
120 *> INCY is INTEGER
121 *> On entry, INCY specifies the increment for the elements of
122 *> Y. INCY must not be zero.
123 *> \endverbatim
124 *
125 * Authors:
126 * ========
127 *
128 *> \author Univ. of Tennessee
129 *> \author Univ. of California Berkeley
130 *> \author Univ. of Colorado Denver
131 *> \author NAG Ltd.
132 *
133 *> \date November 2011
134 *
135 *> \ingroup single_blas_level2
136 *
137 *> \par Further Details:
138 * =====================
139 *>
140 *> \verbatim
141 *>
142 *> Level 2 Blas routine.
143 *> The vector and matrix arguments are not referenced when N = 0, or M = 0
144 *>
145 *> -- Written on 22-October-1986.
146 *> Jack Dongarra, Argonne National Lab.
147 *> Jeremy Du Croz, Nag Central Office.
148 *> Sven Hammarling, Nag Central Office.
149 *> Richard Hanson, Sandia National Labs.
150 *> \endverbatim
151 *>
152 * =====================================================================
153  SUBROUTINE ssymv(UPLO,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
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  REAL ALPHA,BETA
162  INTEGER INCX,INCY,LDA,N
163  CHARACTER UPLO
164 * ..
165 * .. Array Arguments ..
166  REAL A(lda,*),X(*),Y(*)
167 * ..
168 *
169 * =====================================================================
170 *
171 * .. Parameters ..
172  REAL ONE,ZERO
173  parameter(one=1.0e+0,zero=0.0e+0)
174 * ..
175 * .. Local Scalars ..
176  REAL 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('SSYMV ',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 SSYMV .
332 *
333  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine ssymv(UPLO, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
SSYMV
Definition: ssymv.f:154