LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
dsbmv.f
Go to the documentation of this file.
1 *> \brief \b DSBMV
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 DSBMV(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
12 *
13 * .. Scalar Arguments ..
14 * DOUBLE PRECISION ALPHA,BETA
15 * INTEGER INCX,INCY,K,LDA,N
16 * CHARACTER UPLO
17 * ..
18 * .. Array Arguments ..
19 * DOUBLE PRECISION A(LDA,*),X(*),Y(*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> DSBMV 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 band matrix, with k super-diagonals.
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 band matrix A is being supplied as
44 *> follows:
45 *>
46 *> UPLO = 'U' or 'u' The upper triangular part of A is
47 *> being supplied.
48 *>
49 *> UPLO = 'L' or 'l' The lower triangular part of A is
50 *> being supplied.
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] K
61 *> \verbatim
62 *> K is INTEGER
63 *> On entry, K specifies the number of super-diagonals of the
64 *> matrix A. K must satisfy 0 .le. K.
65 *> \endverbatim
66 *>
67 *> \param[in] ALPHA
68 *> \verbatim
69 *> ALPHA is DOUBLE PRECISION.
70 *> On entry, ALPHA specifies the scalar alpha.
71 *> \endverbatim
72 *>
73 *> \param[in] A
74 *> \verbatim
75 *> A is DOUBLE PRECISION array of DIMENSION ( LDA, n ).
76 *> Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
77 *> by n part of the array A must contain the upper triangular
78 *> band part of the symmetric matrix, supplied column by
79 *> column, with the leading diagonal of the matrix in row
80 *> ( k + 1 ) of the array, the first super-diagonal starting at
81 *> position 2 in row k, and so on. The top left k by k triangle
82 *> of the array A is not referenced.
83 *> The following program segment will transfer the upper
84 *> triangular part of a symmetric band matrix from conventional
85 *> full matrix storage to band storage:
86 *>
87 *> DO 20, J = 1, N
88 *> M = K + 1 - J
89 *> DO 10, I = MAX( 1, J - K ), J
90 *> A( M + I, J ) = matrix( I, J )
91 *> 10 CONTINUE
92 *> 20 CONTINUE
93 *>
94 *> Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
95 *> by n part of the array A must contain the lower triangular
96 *> band part of the symmetric matrix, supplied column by
97 *> column, with the leading diagonal of the matrix in row 1 of
98 *> the array, the first sub-diagonal starting at position 1 in
99 *> row 2, and so on. The bottom right k by k triangle of the
100 *> array A is not referenced.
101 *> The following program segment will transfer the lower
102 *> triangular part of a symmetric band matrix from conventional
103 *> full matrix storage to band storage:
104 *>
105 *> DO 20, J = 1, N
106 *> M = 1 - J
107 *> DO 10, I = J, MIN( N, J + K )
108 *> A( M + I, J ) = matrix( I, J )
109 *> 10 CONTINUE
110 *> 20 CONTINUE
111 *> \endverbatim
112 *>
113 *> \param[in] LDA
114 *> \verbatim
115 *> LDA is INTEGER
116 *> On entry, LDA specifies the first dimension of A as declared
117 *> in the calling (sub) program. LDA must be at least
118 *> ( k + 1 ).
119 *> \endverbatim
120 *>
121 *> \param[in] X
122 *> \verbatim
123 *> X is DOUBLE PRECISION array of DIMENSION at least
124 *> ( 1 + ( n - 1 )*abs( INCX ) ).
125 *> Before entry, the incremented array X must contain the
126 *> vector x.
127 *> \endverbatim
128 *>
129 *> \param[in] INCX
130 *> \verbatim
131 *> INCX is INTEGER
132 *> On entry, INCX specifies the increment for the elements of
133 *> X. INCX must not be zero.
134 *> \endverbatim
135 *>
136 *> \param[in] BETA
137 *> \verbatim
138 *> BETA is DOUBLE PRECISION.
139 *> On entry, BETA specifies the scalar beta.
140 *> \endverbatim
141 *>
142 *> \param[in,out] Y
143 *> \verbatim
144 *> Y is DOUBLE PRECISION array of DIMENSION at least
145 *> ( 1 + ( n - 1 )*abs( INCY ) ).
146 *> Before entry, the incremented array Y must contain the
147 *> vector y. On exit, Y is overwritten by the updated vector y.
148 *> \endverbatim
149 *>
150 *> \param[in] INCY
151 *> \verbatim
152 *> INCY is INTEGER
153 *> On entry, INCY specifies the increment for the elements of
154 *> Y. INCY must not be zero.
155 *> \endverbatim
156 *
157 * Authors:
158 * ========
159 *
160 *> \author Univ. of Tennessee
161 *> \author Univ. of California Berkeley
162 *> \author Univ. of Colorado Denver
163 *> \author NAG Ltd.
164 *
165 *> \date November 2011
166 *
167 *> \ingroup double_blas_level2
168 *
169 *> \par Further Details:
170 * =====================
171 *>
172 *> \verbatim
173 *>
174 *> Level 2 Blas routine.
175 *> The vector and matrix arguments are not referenced when N = 0, or M = 0
176 *>
177 *> -- Written on 22-October-1986.
178 *> Jack Dongarra, Argonne National Lab.
179 *> Jeremy Du Croz, Nag Central Office.
180 *> Sven Hammarling, Nag Central Office.
181 *> Richard Hanson, Sandia National Labs.
182 *> \endverbatim
183 *>
184 * =====================================================================
185  SUBROUTINE dsbmv(UPLO,N,K,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
186 *
187 * -- Reference BLAS level2 routine (version 3.4.0) --
188 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
189 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
190 * November 2011
191 *
192 * .. Scalar Arguments ..
193  DOUBLE PRECISION ALPHA,BETA
194  INTEGER INCX,INCY,K,LDA,N
195  CHARACTER UPLO
196 * ..
197 * .. Array Arguments ..
198  DOUBLE PRECISION A(lda,*),X(*),Y(*)
199 * ..
200 *
201 * =====================================================================
202 *
203 * .. Parameters ..
204  DOUBLE PRECISION ONE,ZERO
205  parameter(one=1.0d+0,zero=0.0d+0)
206 * ..
207 * .. Local Scalars ..
208  DOUBLE PRECISION TEMP1,TEMP2
209  INTEGER I,INFO,IX,IY,J,JX,JY,KPLUS1,KX,KY,L
210 * ..
211 * .. External Functions ..
212  LOGICAL LSAME
213  EXTERNAL lsame
214 * ..
215 * .. External Subroutines ..
216  EXTERNAL xerbla
217 * ..
218 * .. Intrinsic Functions ..
219  INTRINSIC max,min
220 * ..
221 *
222 * Test the input parameters.
223 *
224  info = 0
225  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
226  info = 1
227  ELSE IF (n.LT.0) THEN
228  info = 2
229  ELSE IF (k.LT.0) THEN
230  info = 3
231  ELSE IF (lda.LT. (k+1)) THEN
232  info = 6
233  ELSE IF (incx.EQ.0) THEN
234  info = 8
235  ELSE IF (incy.EQ.0) THEN
236  info = 11
237  END IF
238  IF (info.NE.0) THEN
239  CALL xerbla('DSBMV ',info)
240  RETURN
241  END IF
242 *
243 * Quick return if possible.
244 *
245  IF ((n.EQ.0) .OR. ((alpha.EQ.zero).AND. (beta.EQ.one))) RETURN
246 *
247 * Set up the start points in X and Y.
248 *
249  IF (incx.GT.0) THEN
250  kx = 1
251  ELSE
252  kx = 1 - (n-1)*incx
253  END IF
254  IF (incy.GT.0) THEN
255  ky = 1
256  ELSE
257  ky = 1 - (n-1)*incy
258  END IF
259 *
260 * Start the operations. In this version the elements of the array A
261 * are accessed sequentially with one pass through A.
262 *
263 * First form y := beta*y.
264 *
265  IF (beta.NE.one) THEN
266  IF (incy.EQ.1) THEN
267  IF (beta.EQ.zero) THEN
268  DO 10 i = 1,n
269  y(i) = zero
270  10 CONTINUE
271  ELSE
272  DO 20 i = 1,n
273  y(i) = beta*y(i)
274  20 CONTINUE
275  END IF
276  ELSE
277  iy = ky
278  IF (beta.EQ.zero) THEN
279  DO 30 i = 1,n
280  y(iy) = zero
281  iy = iy + incy
282  30 CONTINUE
283  ELSE
284  DO 40 i = 1,n
285  y(iy) = beta*y(iy)
286  iy = iy + incy
287  40 CONTINUE
288  END IF
289  END IF
290  END IF
291  IF (alpha.EQ.zero) RETURN
292  IF (lsame(uplo,'U')) THEN
293 *
294 * Form y when upper triangle of A is stored.
295 *
296  kplus1 = k + 1
297  IF ((incx.EQ.1) .AND. (incy.EQ.1)) THEN
298  DO 60 j = 1,n
299  temp1 = alpha*x(j)
300  temp2 = zero
301  l = kplus1 - j
302  DO 50 i = max(1,j-k),j - 1
303  y(i) = y(i) + temp1*a(l+i,j)
304  temp2 = temp2 + a(l+i,j)*x(i)
305  50 CONTINUE
306  y(j) = y(j) + temp1*a(kplus1,j) + alpha*temp2
307  60 CONTINUE
308  ELSE
309  jx = kx
310  jy = ky
311  DO 80 j = 1,n
312  temp1 = alpha*x(jx)
313  temp2 = zero
314  ix = kx
315  iy = ky
316  l = kplus1 - j
317  DO 70 i = max(1,j-k),j - 1
318  y(iy) = y(iy) + temp1*a(l+i,j)
319  temp2 = temp2 + a(l+i,j)*x(ix)
320  ix = ix + incx
321  iy = iy + incy
322  70 CONTINUE
323  y(jy) = y(jy) + temp1*a(kplus1,j) + alpha*temp2
324  jx = jx + incx
325  jy = jy + incy
326  IF (j.GT.k) THEN
327  kx = kx + incx
328  ky = ky + incy
329  END IF
330  80 CONTINUE
331  END IF
332  ELSE
333 *
334 * Form y when lower triangle of A is stored.
335 *
336  IF ((incx.EQ.1) .AND. (incy.EQ.1)) THEN
337  DO 100 j = 1,n
338  temp1 = alpha*x(j)
339  temp2 = zero
340  y(j) = y(j) + temp1*a(1,j)
341  l = 1 - j
342  DO 90 i = j + 1,min(n,j+k)
343  y(i) = y(i) + temp1*a(l+i,j)
344  temp2 = temp2 + a(l+i,j)*x(i)
345  90 CONTINUE
346  y(j) = y(j) + alpha*temp2
347  100 CONTINUE
348  ELSE
349  jx = kx
350  jy = ky
351  DO 120 j = 1,n
352  temp1 = alpha*x(jx)
353  temp2 = zero
354  y(jy) = y(jy) + temp1*a(1,j)
355  l = 1 - j
356  ix = jx
357  iy = jy
358  DO 110 i = j + 1,min(n,j+k)
359  ix = ix + incx
360  iy = iy + incy
361  y(iy) = y(iy) + temp1*a(l+i,j)
362  temp2 = temp2 + a(l+i,j)*x(ix)
363  110 CONTINUE
364  y(jy) = y(jy) + alpha*temp2
365  jx = jx + incx
366  jy = jy + incy
367  120 CONTINUE
368  END IF
369  END IF
370 *
371  RETURN
372 *
373 * End of DSBMV .
374 *
375  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine dsbmv(UPLO, N, K, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
DSBMV
Definition: dsbmv.f:186