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