LAPACK  3.4.2
LAPACK: Linear Algebra PACKage
 All Files Functions Groups
dspmv.f
Go to the documentation of this file.
1 *> \brief \b DSPMV
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 DSPMV(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
12 *
13 * .. Scalar Arguments ..
14 * DOUBLE PRECISION ALPHA,BETA
15 * INTEGER INCX,INCY,N
16 * CHARACTER UPLO
17 * ..
18 * .. Array Arguments ..
19 * DOUBLE PRECISION AP(*),X(*),Y(*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> DSPMV 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, supplied in packed form.
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 matrix A is supplied in the packed
44 *> array AP as follows:
45 *>
46 *> UPLO = 'U' or 'u' The upper triangular part of A is
47 *> supplied in AP.
48 *>
49 *> UPLO = 'L' or 'l' The lower triangular part of A is
50 *> supplied in AP.
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 DOUBLE PRECISION.
63 *> On entry, ALPHA specifies the scalar alpha.
64 *> \endverbatim
65 *>
66 *> \param[in] AP
67 *> \verbatim
68 *> AP is DOUBLE PRECISION array of DIMENSION at least
69 *> ( ( n*( n + 1 ) )/2 ).
70 *> Before entry with UPLO = 'U' or 'u', the array AP must
71 *> contain the upper triangular part of the symmetric matrix
72 *> packed sequentially, column by column, so that AP( 1 )
73 *> contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 1, 2 )
74 *> and a( 2, 2 ) respectively, and so on.
75 *> Before entry with UPLO = 'L' or 'l', the array AP must
76 *> contain the lower triangular part of the symmetric matrix
77 *> packed sequentially, column by column, so that AP( 1 )
78 *> contains a( 1, 1 ), AP( 2 ) and AP( 3 ) contain a( 2, 1 )
79 *> and a( 3, 1 ) respectively, and so on.
80 *> \endverbatim
81 *>
82 *> \param[in] X
83 *> \verbatim
84 *> X is DOUBLE PRECISION array of dimension at least
85 *> ( 1 + ( n - 1 )*abs( INCX ) ).
86 *> Before entry, the incremented array X must contain the n
87 *> element vector x.
88 *> \endverbatim
89 *>
90 *> \param[in] INCX
91 *> \verbatim
92 *> INCX is INTEGER
93 *> On entry, INCX specifies the increment for the elements of
94 *> X. INCX must not be zero.
95 *> \endverbatim
96 *>
97 *> \param[in] BETA
98 *> \verbatim
99 *> BETA is DOUBLE PRECISION.
100 *> On entry, BETA specifies the scalar beta. When BETA is
101 *> supplied as zero then Y need not be set on input.
102 *> \endverbatim
103 *>
104 *> \param[in,out] Y
105 *> \verbatim
106 *> Y is DOUBLE PRECISION array of dimension at least
107 *> ( 1 + ( n - 1 )*abs( INCY ) ).
108 *> Before entry, the incremented array Y must contain the n
109 *> element vector y. On exit, Y is overwritten by the updated
110 *> vector y.
111 *> \endverbatim
112 *>
113 *> \param[in] INCY
114 *> \verbatim
115 *> INCY is INTEGER
116 *> On entry, INCY specifies the increment for the elements of
117 *> Y. INCY must not be zero.
118 *> \endverbatim
119 *
120 * Authors:
121 * ========
122 *
123 *> \author Univ. of Tennessee
124 *> \author Univ. of California Berkeley
125 *> \author Univ. of Colorado Denver
126 *> \author NAG Ltd.
127 *
128 *> \date November 2011
129 *
130 *> \ingroup double_blas_level2
131 *
132 *> \par Further Details:
133 * =====================
134 *>
135 *> \verbatim
136 *>
137 *> Level 2 Blas routine.
138 *> The vector and matrix arguments are not referenced when N = 0, or M = 0
139 *>
140 *> -- Written on 22-October-1986.
141 *> Jack Dongarra, Argonne National Lab.
142 *> Jeremy Du Croz, Nag Central Office.
143 *> Sven Hammarling, Nag Central Office.
144 *> Richard Hanson, Sandia National Labs.
145 *> \endverbatim
146 *>
147 * =====================================================================
148  SUBROUTINE dspmv(UPLO,N,ALPHA,AP,X,INCX,BETA,Y,INCY)
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  DOUBLE PRECISION alpha,beta
157  INTEGER incx,incy,n
158  CHARACTER uplo
159 * ..
160 * .. Array Arguments ..
161  DOUBLE PRECISION ap(*),x(*),y(*)
162 * ..
163 *
164 * =====================================================================
165 *
166 * .. Parameters ..
167  DOUBLE PRECISION one,zero
168  parameter(one=1.0d+0,zero=0.0d+0)
169 * ..
170 * .. Local Scalars ..
171  DOUBLE PRECISION 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('DSPMV ',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 DSPMV .
330 *
331  END