LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine stbmv ( character  UPLO,
character  TRANS,
character  DIAG,
integer  N,
integer  K,
real, dimension(lda,*)  A,
integer  LDA,
real, dimension(*)  X,
integer  INCX 
)

STBMV

Purpose:
 STBMV  performs one of the matrix-vector operations

    x := A*x,   or   x := A**T*x,

 where x is an n element vector and  A is an n by n unit, or non-unit,
 upper or lower triangular band matrix, with ( k + 1 ) diagonals.
Parameters
[in]UPLO
          UPLO is CHARACTER*1
           On entry, UPLO specifies whether the matrix is an upper or
           lower triangular matrix as follows:

              UPLO = 'U' or 'u'   A is an upper triangular matrix.

              UPLO = 'L' or 'l'   A is a lower triangular matrix.
[in]TRANS
          TRANS is CHARACTER*1
           On entry, TRANS specifies the operation to be performed as
           follows:

              TRANS = 'N' or 'n'   x := A*x.

              TRANS = 'T' or 't'   x := A**T*x.

              TRANS = 'C' or 'c'   x := A**T*x.
[in]DIAG
          DIAG is CHARACTER*1
           On entry, DIAG specifies whether or not A is unit
           triangular as follows:

              DIAG = 'U' or 'u'   A is assumed to be unit triangular.

              DIAG = 'N' or 'n'   A is not assumed to be unit
                                  triangular.
[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 with UPLO = 'U' or 'u', K specifies the number of
           super-diagonals of the matrix A.
           On entry with UPLO = 'L' or 'l', K specifies the number of
           sub-diagonals of the matrix A.
           K must satisfy  0 .le. K.
[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 matrix of coefficients, 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 an upper
           triangular 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 matrix of coefficients, 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 a lower
           triangular 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

           Note that when DIAG = 'U' or 'u' the elements of the array A
           corresponding to the diagonal elements of the matrix are not
           referenced, but are assumed to be unity.
[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,out]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. On exit, X is overwritten with the
           tranformed vector x.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX 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 188 of file stbmv.f.

188 *
189 * -- Reference BLAS level2 routine (version 3.4.0) --
190 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
191 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
192 * November 2011
193 *
194 * .. Scalar Arguments ..
195  INTEGER incx,k,lda,n
196  CHARACTER diag,trans,uplo
197 * ..
198 * .. Array Arguments ..
199  REAL a(lda,*),x(*)
200 * ..
201 *
202 * =====================================================================
203 *
204 * .. Parameters ..
205  REAL zero
206  parameter(zero=0.0e+0)
207 * ..
208 * .. Local Scalars ..
209  REAL temp
210  INTEGER i,info,ix,j,jx,kplus1,kx,l
211  LOGICAL nounit
212 * ..
213 * .. External Functions ..
214  LOGICAL lsame
215  EXTERNAL lsame
216 * ..
217 * .. External Subroutines ..
218  EXTERNAL xerbla
219 * ..
220 * .. Intrinsic Functions ..
221  INTRINSIC max,min
222 * ..
223 *
224 * Test the input parameters.
225 *
226  info = 0
227  IF (.NOT.lsame(uplo,'U') .AND. .NOT.lsame(uplo,'L')) THEN
228  info = 1
229  ELSE IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
230  + .NOT.lsame(trans,'C')) THEN
231  info = 2
232  ELSE IF (.NOT.lsame(diag,'U') .AND. .NOT.lsame(diag,'N')) THEN
233  info = 3
234  ELSE IF (n.LT.0) THEN
235  info = 4
236  ELSE IF (k.LT.0) THEN
237  info = 5
238  ELSE IF (lda.LT. (k+1)) THEN
239  info = 7
240  ELSE IF (incx.EQ.0) THEN
241  info = 9
242  END IF
243  IF (info.NE.0) THEN
244  CALL xerbla('STBMV ',info)
245  RETURN
246  END IF
247 *
248 * Quick return if possible.
249 *
250  IF (n.EQ.0) RETURN
251 *
252  nounit = lsame(diag,'N')
253 *
254 * Set up the start point in X if the increment is not unity. This
255 * will be ( N - 1 )*INCX too small for descending loops.
256 *
257  IF (incx.LE.0) THEN
258  kx = 1 - (n-1)*incx
259  ELSE IF (incx.NE.1) THEN
260  kx = 1
261  END IF
262 *
263 * Start the operations. In this version the elements of A are
264 * accessed sequentially with one pass through A.
265 *
266  IF (lsame(trans,'N')) THEN
267 *
268 * Form x := A*x.
269 *
270  IF (lsame(uplo,'U')) THEN
271  kplus1 = k + 1
272  IF (incx.EQ.1) THEN
273  DO 20 j = 1,n
274  IF (x(j).NE.zero) THEN
275  temp = x(j)
276  l = kplus1 - j
277  DO 10 i = max(1,j-k),j - 1
278  x(i) = x(i) + temp*a(l+i,j)
279  10 CONTINUE
280  IF (nounit) x(j) = x(j)*a(kplus1,j)
281  END IF
282  20 CONTINUE
283  ELSE
284  jx = kx
285  DO 40 j = 1,n
286  IF (x(jx).NE.zero) THEN
287  temp = x(jx)
288  ix = kx
289  l = kplus1 - j
290  DO 30 i = max(1,j-k),j - 1
291  x(ix) = x(ix) + temp*a(l+i,j)
292  ix = ix + incx
293  30 CONTINUE
294  IF (nounit) x(jx) = x(jx)*a(kplus1,j)
295  END IF
296  jx = jx + incx
297  IF (j.GT.k) kx = kx + incx
298  40 CONTINUE
299  END IF
300  ELSE
301  IF (incx.EQ.1) THEN
302  DO 60 j = n,1,-1
303  IF (x(j).NE.zero) THEN
304  temp = x(j)
305  l = 1 - j
306  DO 50 i = min(n,j+k),j + 1,-1
307  x(i) = x(i) + temp*a(l+i,j)
308  50 CONTINUE
309  IF (nounit) x(j) = x(j)*a(1,j)
310  END IF
311  60 CONTINUE
312  ELSE
313  kx = kx + (n-1)*incx
314  jx = kx
315  DO 80 j = n,1,-1
316  IF (x(jx).NE.zero) THEN
317  temp = x(jx)
318  ix = kx
319  l = 1 - j
320  DO 70 i = min(n,j+k),j + 1,-1
321  x(ix) = x(ix) + temp*a(l+i,j)
322  ix = ix - incx
323  70 CONTINUE
324  IF (nounit) x(jx) = x(jx)*a(1,j)
325  END IF
326  jx = jx - incx
327  IF ((n-j).GE.k) kx = kx - incx
328  80 CONTINUE
329  END IF
330  END IF
331  ELSE
332 *
333 * Form x := A**T*x.
334 *
335  IF (lsame(uplo,'U')) THEN
336  kplus1 = k + 1
337  IF (incx.EQ.1) THEN
338  DO 100 j = n,1,-1
339  temp = x(j)
340  l = kplus1 - j
341  IF (nounit) temp = temp*a(kplus1,j)
342  DO 90 i = j - 1,max(1,j-k),-1
343  temp = temp + a(l+i,j)*x(i)
344  90 CONTINUE
345  x(j) = temp
346  100 CONTINUE
347  ELSE
348  kx = kx + (n-1)*incx
349  jx = kx
350  DO 120 j = n,1,-1
351  temp = x(jx)
352  kx = kx - incx
353  ix = kx
354  l = kplus1 - j
355  IF (nounit) temp = temp*a(kplus1,j)
356  DO 110 i = j - 1,max(1,j-k),-1
357  temp = temp + a(l+i,j)*x(ix)
358  ix = ix - incx
359  110 CONTINUE
360  x(jx) = temp
361  jx = jx - incx
362  120 CONTINUE
363  END IF
364  ELSE
365  IF (incx.EQ.1) THEN
366  DO 140 j = 1,n
367  temp = x(j)
368  l = 1 - j
369  IF (nounit) temp = temp*a(1,j)
370  DO 130 i = j + 1,min(n,j+k)
371  temp = temp + a(l+i,j)*x(i)
372  130 CONTINUE
373  x(j) = temp
374  140 CONTINUE
375  ELSE
376  jx = kx
377  DO 160 j = 1,n
378  temp = x(jx)
379  kx = kx + incx
380  ix = kx
381  l = 1 - j
382  IF (nounit) temp = temp*a(1,j)
383  DO 150 i = j + 1,min(n,j+k)
384  temp = temp + a(l+i,j)*x(ix)
385  ix = ix + incx
386  150 CONTINUE
387  x(jx) = temp
388  jx = jx + incx
389  160 CONTINUE
390  END IF
391  END IF
392  END IF
393 *
394  RETURN
395 *
396 * End of STBMV .
397 *
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: