LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine sspmv ( character  UPLO,
integer  N,
real  ALPHA,
real, dimension(*)  AP,
real, dimension(*)  X,
integer  INCX,
real  BETA,
real, dimension(*)  Y,
integer  INCY 
)

SSPMV

Purpose:
 SSPMV  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, supplied in packed form.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the upper or lower
           triangular part of the matrix A is supplied in the packed
           array AP as follows:

              UPLO = 'U' or 'u'   The upper triangular part of A is
                                  supplied in AP.

              UPLO = 'L' or 'l'   The lower triangular part of A is
                                  supplied in AP.
[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 REAL
           On entry, ALPHA specifies the scalar alpha.
[in]AP
          AP is REAL array of DIMENSION at least
           ( ( n*( n + 1 ) )/2 ).
           Before entry with UPLO = 'U' or 'u', the array AP must
           contain the upper triangular part of the symmetric matrix
           packed sequentially, column by column, so that AP( 1 )
           contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 )
           and a( 2, 2 ) respectively, and so on.
           Before entry with UPLO = 'L' or 'l', the array AP must
           contain the lower triangular part of the symmetric matrix
           packed sequentially, column by column, so that AP( 1 )
           contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 )
           and a( 3, 1 ) respectively, and so on.
[in]X
          X is REAL 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 REAL
           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 REAL 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 149 of file sspmv.f.

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