LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine ssbmv ( character  UPLO,
integer  N,
integer  K,
real  ALPHA,
real, dimension(lda,*)  A,
integer  LDA,
real, dimension(*)  X,
integer  INCX,
real  BETA,
real, dimension(*)  Y,
integer  INCY 
)

SSBMV

Purpose:
 SSBMV  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 band matrix, with k super-diagonals.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the upper or lower
           triangular part of the band matrix A is being supplied as
           follows:

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

              UPLO = 'L' or 'l'   The lower triangular part of A is
                                  being supplied.
[in]N
          N is INTEGER
           On entry, N specifies the order of the matrix A.
           N must be at least zero.
[in]K
          K is INTEGER
           On entry, K specifies the number of super-diagonals of the
           matrix A. K must satisfy  0 .le. K.
[in]ALPHA
          ALPHA is REAL
           On entry, ALPHA specifies the scalar alpha.
[in]A
          A is REAL array of DIMENSION ( LDA, n ).
           Before entry with UPLO = 'U' or 'u', the leading ( k + 1 )
           by n part of the array A must contain the upper triangular
           band part of the symmetric matrix, supplied column by
           column, with the leading diagonal of the matrix in row
           ( k + 1 ) of the array, the first super-diagonal starting at
           position 2 in row k, and so on. The top left k by k triangle
           of the array A is not referenced.
           The following program segment will transfer the upper
           triangular part of a symmetric band matrix from conventional
           full matrix storage to band storage:

                 DO 20, J = 1, N
                    M = K + 1 - J
                    DO 10, I = MAX( 1, J - K ), J
                       A( M + I, J ) = matrix( I, J )
              10    CONTINUE
              20 CONTINUE

           Before entry with UPLO = 'L' or 'l', the leading ( k + 1 )
           by n part of the array A must contain the lower triangular
           band part of the symmetric matrix, supplied column by
           column, with the leading diagonal of the matrix in row 1 of
           the array, the first sub-diagonal starting at position 1 in
           row 2, and so on. The bottom right k by k triangle of the
           array A is not referenced.
           The following program segment will transfer the lower
           triangular part of a symmetric band matrix from conventional
           full matrix storage to band storage:

                 DO 20, J = 1, N
                    M = 1 - J
                    DO 10, I = J, MIN( N, J + K )
                       A( M + I, J ) = matrix( I, J )
              10    CONTINUE
              20 CONTINUE
[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
           ( k + 1 ).
[in]X
          X is REAL array of DIMENSION at least
           ( 1 + ( n - 1 )*abs( INCX ) ).
           Before entry, the incremented array X must contain the
           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.
[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
           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 186 of file ssbmv.f.

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  REAL alpha,beta
194  INTEGER incx,incy,k,lda,n
195  CHARACTER uplo
196 * ..
197 * .. Array Arguments ..
198  REAL a(lda,*),x(*),y(*)
199 * ..
200 *
201 * =====================================================================
202 *
203 * .. Parameters ..
204  REAL one,zero
205  parameter(one=1.0e+0,zero=0.0e+0)
206 * ..
207 * .. Local Scalars ..
208  REAL 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('SSBMV ',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 SSBMV .
374 *
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: