LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine dgbmv ( character  TRANS,
integer  M,
integer  N,
integer  KL,
integer  KU,
double precision  ALPHA,
double precision, dimension(lda,*)  A,
integer  LDA,
double precision, dimension(*)  X,
integer  INCX,
double precision  BETA,
double precision, dimension(*)  Y,
integer  INCY 
)

DGBMV

Purpose:
 DGBMV  performs one of the matrix-vector operations

    y := alpha*A*x + beta*y,   or   y := alpha*A**T*x + beta*y,

 where alpha and beta are scalars, x and y are vectors and A is an
 m by n band matrix, with kl sub-diagonals and ku super-diagonals.
Parameters
[in]TRANS
          TRANS is CHARACTER*1
           On entry, TRANS specifies the operation to be performed as
           follows:

              TRANS = 'N' or 'n'   y := alpha*A*x + beta*y.

              TRANS = 'T' or 't'   y := alpha*A**T*x + beta*y.

              TRANS = 'C' or 'c'   y := alpha*A**T*x + beta*y.
[in]M
          M is INTEGER
           On entry, M specifies the number of rows of the matrix A.
           M must be at least zero.
[in]N
          N is INTEGER
           On entry, N specifies the number of columns of the matrix A.
           N must be at least zero.
[in]KL
          KL is INTEGER
           On entry, KL specifies the number of sub-diagonals of the
           matrix A. KL must satisfy  0 .le. KL.
[in]KU
          KU is INTEGER
           On entry, KU specifies the number of super-diagonals of the
           matrix A. KU must satisfy  0 .le. KU.
[in]ALPHA
          ALPHA is DOUBLE PRECISION.
           On entry, ALPHA specifies the scalar alpha.
[in]A
          A is DOUBLE PRECISION array of DIMENSION ( LDA, n ).
           Before entry, the leading ( kl + ku + 1 ) by n part of the
           array A must contain the matrix of coefficients, supplied
           column by column, with the leading diagonal of the matrix in
           row ( ku + 1 ) of the array, the first super-diagonal
           starting at position 2 in row ku, the first sub-diagonal
           starting at position 1 in row ( ku + 2 ), and so on.
           Elements in the array A that do not correspond to elements
           in the band matrix (such as the top left ku by ku triangle)
           are not referenced.
           The following program segment will transfer a band matrix
           from conventional full matrix storage to band storage:

                 DO 20, J = 1, N
                    K = KU + 1 - J
                    DO 10, I = MAX( 1, J - KU ), MIN( M, J + KL )
                       A( K + 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
           ( kl + ku + 1 ).
[in]X
          X is DOUBLE PRECISION array of DIMENSION at least
           ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'
           and at least
           ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.
           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 DOUBLE PRECISION.
           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 DOUBLE PRECISION array of DIMENSION at least
           ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'
           and at least
           ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.
           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 2015
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 187 of file dgbmv.f.

187 *
188 * -- Reference BLAS level2 routine (version 3.6.0) --
189 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
190 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
191 * November 2015
192 *
193 * .. Scalar Arguments ..
194  DOUBLE PRECISION alpha,beta
195  INTEGER incx,incy,kl,ku,lda,m,n
196  CHARACTER trans
197 * ..
198 * .. Array Arguments ..
199  DOUBLE PRECISION a(lda,*),x(*),y(*)
200 * ..
201 *
202 * =====================================================================
203 *
204 * .. Parameters ..
205  DOUBLE PRECISION one,zero
206  parameter(one=1.0d+0,zero=0.0d+0)
207 * ..
208 * .. Local Scalars ..
209  DOUBLE PRECISION temp
210  INTEGER i,info,ix,iy,j,jx,jy,k,kup1,kx,ky,lenx,leny
211 * ..
212 * .. External Functions ..
213  LOGICAL lsame
214  EXTERNAL lsame
215 * ..
216 * .. External Subroutines ..
217  EXTERNAL xerbla
218 * ..
219 * .. Intrinsic Functions ..
220  INTRINSIC max,min
221 * ..
222 *
223 * Test the input parameters.
224 *
225  info = 0
226  IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
227  + .NOT.lsame(trans,'C')) THEN
228  info = 1
229  ELSE IF (m.LT.0) THEN
230  info = 2
231  ELSE IF (n.LT.0) THEN
232  info = 3
233  ELSE IF (kl.LT.0) THEN
234  info = 4
235  ELSE IF (ku.LT.0) THEN
236  info = 5
237  ELSE IF (lda.LT. (kl+ku+1)) THEN
238  info = 8
239  ELSE IF (incx.EQ.0) THEN
240  info = 10
241  ELSE IF (incy.EQ.0) THEN
242  info = 13
243  END IF
244  IF (info.NE.0) THEN
245  CALL xerbla('DGBMV ',info)
246  RETURN
247  END IF
248 *
249 * Quick return if possible.
250 *
251  IF ((m.EQ.0) .OR. (n.EQ.0) .OR.
252  + ((alpha.EQ.zero).AND. (beta.EQ.one))) RETURN
253 *
254 * Set LENX and LENY, the lengths of the vectors x and y, and set
255 * up the start points in X and Y.
256 *
257  IF (lsame(trans,'N')) THEN
258  lenx = n
259  leny = m
260  ELSE
261  lenx = m
262  leny = n
263  END IF
264  IF (incx.GT.0) THEN
265  kx = 1
266  ELSE
267  kx = 1 - (lenx-1)*incx
268  END IF
269  IF (incy.GT.0) THEN
270  ky = 1
271  ELSE
272  ky = 1 - (leny-1)*incy
273  END IF
274 *
275 * Start the operations. In this version the elements of A are
276 * accessed sequentially with one pass through the band part of A.
277 *
278 * First form y := beta*y.
279 *
280  IF (beta.NE.one) THEN
281  IF (incy.EQ.1) THEN
282  IF (beta.EQ.zero) THEN
283  DO 10 i = 1,leny
284  y(i) = zero
285  10 CONTINUE
286  ELSE
287  DO 20 i = 1,leny
288  y(i) = beta*y(i)
289  20 CONTINUE
290  END IF
291  ELSE
292  iy = ky
293  IF (beta.EQ.zero) THEN
294  DO 30 i = 1,leny
295  y(iy) = zero
296  iy = iy + incy
297  30 CONTINUE
298  ELSE
299  DO 40 i = 1,leny
300  y(iy) = beta*y(iy)
301  iy = iy + incy
302  40 CONTINUE
303  END IF
304  END IF
305  END IF
306  IF (alpha.EQ.zero) RETURN
307  kup1 = ku + 1
308  IF (lsame(trans,'N')) THEN
309 *
310 * Form y := alpha*A*x + y.
311 *
312  jx = kx
313  IF (incy.EQ.1) THEN
314  DO 60 j = 1,n
315  temp = alpha*x(jx)
316  k = kup1 - j
317  DO 50 i = max(1,j-ku),min(m,j+kl)
318  y(i) = y(i) + temp*a(k+i,j)
319  50 CONTINUE
320  jx = jx + incx
321  60 CONTINUE
322  ELSE
323  DO 80 j = 1,n
324  temp = alpha*x(jx)
325  iy = ky
326  k = kup1 - j
327  DO 70 i = max(1,j-ku),min(m,j+kl)
328  y(iy) = y(iy) + temp*a(k+i,j)
329  iy = iy + incy
330  70 CONTINUE
331  jx = jx + incx
332  IF (j.GT.ku) ky = ky + incy
333  80 CONTINUE
334  END IF
335  ELSE
336 *
337 * Form y := alpha*A**T*x + y.
338 *
339  jy = ky
340  IF (incx.EQ.1) THEN
341  DO 100 j = 1,n
342  temp = zero
343  k = kup1 - j
344  DO 90 i = max(1,j-ku),min(m,j+kl)
345  temp = temp + a(k+i,j)*x(i)
346  90 CONTINUE
347  y(jy) = y(jy) + alpha*temp
348  jy = jy + incy
349  100 CONTINUE
350  ELSE
351  DO 120 j = 1,n
352  temp = zero
353  ix = kx
354  k = kup1 - j
355  DO 110 i = max(1,j-ku),min(m,j+kl)
356  temp = temp + a(k+i,j)*x(ix)
357  ix = ix + incx
358  110 CONTINUE
359  y(jy) = y(jy) + alpha*temp
360  jy = jy + incy
361  IF (j.GT.ku) kx = kx + incx
362  120 CONTINUE
363  END IF
364  END IF
365 *
366  RETURN
367 *
368 * End of DGBMV .
369 *
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: