1STBMV(1)                         BLAS routine                         STBMV(1)
2
3
4

NAME

6       STBMV - one of the matrix-vector operations   x := A*x, or x := A'*x,
7

SYNOPSIS

9       SUBROUTINE STBMV(UPLO,TRANS,DIAG,N,K,A,LDA,X,INCX)
10
11           INTEGER                                        INCX,K,LDA,N
12
13           CHARACTER                                      DIAG,TRANS,UPLO
14
15           REAL                                           A(LDA,*),X(*)
16

PURPOSE

18       STBMV  performs one of the matrix-vector operations
19
20       where  x  is an n element vector and  A is an n by n unit, or non-unit,
21       upper or lower triangular band matrix, with ( k + 1 ) diagonals.
22
23

ARGUMENTS

25       UPLO   - CHARACTER*1.
26              On entry, UPLO specifies whether the matrix is an upper or lower
27              triangular matrix as follows:
28
29              UPLO = 'U' or 'u'   A is an upper triangular matrix.
30
31              UPLO = 'L' or 'l'   A is a lower triangular matrix.
32
33              Unchanged on exit.
34
35       TRANS  - CHARACTER*1.
36              On  entry, TRANS specifies the operation to be performed as fol‐
37              lows:
38
39              TRANS = 'N' or 'n'   x := A*x.
40
41              TRANS = 'T' or 't'   x := A'*x.
42
43              TRANS = 'C' or 'c'   x := A'*x.
44
45              Unchanged on exit.
46
47       DIAG   - CHARACTER*1.
48              On entry, DIAG specifies whether or not A is unit triangular  as
49              follows:
50
51              DIAG = 'U' or 'u'   A is assumed to be unit triangular.
52
53              DIAG = 'N' or 'n'   A is not assumed to be unit triangular.
54
55              Unchanged on exit.
56
57       N      - INTEGER.
58              On  entry,  N specifies the order of the matrix A.  N must be at
59              least zero.  Unchanged on exit.
60
61       K      - INTEGER.
62              On entry with UPLO = 'U' or  'u',  K  specifies  the  number  of
63              super-diagonals  of  the  matrix A.  On entry with UPLO = 'L' or
64              'l', K specifies the number of sub-diagonals of the matrix A.  K
65              must satisfy  0 .le. K.  Unchanged on exit.
66
67       A      - REAL             array of DIMENSION ( LDA, n ).
68              Before  entry with UPLO = 'U' or 'u', the leading ( k + 1 ) by n
69              part of the array A must contain the upper triangular band  part
70              of  the  matrix of coefficients, supplied column by column, with
71              the leading diagonal of the matrix in row (  k  +  1  )  of  the
72              array, the first super-diagonal starting at position 2 in row k,
73              and so on. The top left k by k triangle of the array  A  is  not
74              referenced.   The  following  program  segment  will transfer an
75              upper triangular band matrix from conventional full matrix stor‐
76              age to band storage:
77
78              DO 20, J = 1, N M = K + 1 - J DO 10, I = MAX( 1, J - K ), J A( M
79              + I, J ) = matrix( I, J ) 10    CONTINUE 20 CONTINUE
80
81              Before entry with UPLO = 'L' or 'l', the leading ( k + 1 ) by  n
82              part  of the array A must contain the lower triangular band part
83              of the matrix of coefficients, supplied column by  column,  with
84              the  leading  diagonal  of the matrix in row 1 of the array, the
85              first sub-diagonal starting at position 1 in row 2, and  so  on.
86              The  bottom  right  k by k triangle of the array A is not refer‐
87              enced.  The following program segment will transfer a lower tri‐
88              angular  band  matrix  from  conventional full matrix storage to
89              band storage:
90
91              DO 20, J = 1, N M = 1 - J DO 10, I = J, MIN( N, J + K ) A(  M  +
92              I, J ) = matrix( I, J ) 10    CONTINUE 20 CONTINUE
93
94              Note  that  when  DIAG  = 'U' or 'u' the elements of the array A
95              corresponding to the diagonal elements of  the  matrix  are  not
96              referenced, but are assumed to be unity.  Unchanged on exit.
97
98       LDA    - INTEGER.
99              On  entry, LDA specifies the first dimension of A as declared in
100              the calling (sub) program. LDA must be at  least  (  k  +  1  ).
101              Unchanged on exit.
102
103       X      - REAL             array of dimension at least
104              (  1  +  ( n - 1 )*abs( INCX ) ).  Before entry, the incremented
105              array X must contain the n element vector x. On exit, X is over‐
106              written with the tranformed vector x.
107
108       INCX   - INTEGER.
109              On  entry,  INCX  specifies the increment for the elements of X.
110              INCX must not be zero.  Unchanged on exit.
111
112              Level 2 Blas routine.
113
114              -- Written on 22-October-1986.  Jack Dongarra, Argonne  National
115              Lab.   Jeremy Du Croz, Nag Central Office.  Sven Hammarling, Nag
116              Central Office.  Richard Hanson, Sandia National Labs.
117
118
119
120BLAS routine                     November 2006                        STBMV(1)
Impressum