1SLA_GBAMV(1)LAPACK routine (version 3.2) SLA_GBAMV(1)
2
3
4
6 SLA_GBAMV - performs one of the matrix-vector operations y :=
7 alpha*abs(A)*abs(x) + beta*abs(y),
8
10 SUBROUTINE SLA_GBAMV( TRANS, M, N, KL, KU, ALPHA, AB, LDAB, X, INCX,
11 BETA, Y, INCY )
12
13 IMPLICIT NONE
14
15 REAL ALPHA, BETA
16
17 INTEGER INCX, INCY, LDAB, M, N, KL, KU, TRANS
18
19 REAL AB( LDAB, * ), X( * ), Y( * )
20
22 SLA_GEAMV performs one of the matrix-vector operations
23 or y := alpha*abs(A)'*abs(x) + beta*abs(y),
24 where alpha and beta are scalars, x and y are vectors and A is an m by
25 n matrix.
26 This function is primarily used in calculating error bounds. To pro‐
27 tect against underflow during evaluation, components in the resulting
28 vector are perturbed away from zero by (N+1) times the underflow
29 threshold. To prevent unnecessarily large errors for block-structure
30 embedded in general matrices,
31 "symbolically" zero components are not perturbed. A zero entry is con‐
32 sidered "symbolic" if all multiplications involved in computing that
33 entry have at least one zero multiplicand.
34
36 TRANS - INTEGER
37 On entry, TRANS specifies the operation to be performed as fol‐
38 lows:
39
40 BLAS_NO_TRANS y := alpha*abs(A)*abs(x) + beta*abs(y)
41 BLAS_TRANS y := alpha*abs(A')*abs(x) +
42 beta*abs(y)
43 BLAS_CONJ_TRANS y := alpha*abs(A')*abs(x) +
44 beta*abs(y) Unchanged on exit.
45
46 M - INTEGER
47 On entry, M specifies the number of rows of the matrix A. M
48 must be at least zero. Unchanged on exit.
49
50 N - INTEGER
51 On entry, N specifies the number of columns of the matrix A. N
52 must be at least zero. Unchanged on exit.
53
54 KL - INTEGER
55 The number of subdiagonals within the band of A. KL >= 0.
56
57 KU - INTEGER
58 The number of superdiagonals within the band of A. KU >= 0.
59
60 ALPHA - REAL
61 On entry, ALPHA specifies the scalar alpha. Unchanged on exit.
62
63 A - REAL array of DIMENSION ( LDA, n )
64 Before entry, the leading m by n part of the array A must con‐
65 tain the matrix of coefficients. Unchanged on exit.
66
67 LDA - INTEGER
68 On entry, LDA specifies the first dimension of A as declared in
69 the calling (sub) program. LDA must be at least max( 1, m ).
70 Unchanged on exit.
71
72 X - REAL array of DIMENSION at least
73 ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n' and at
74 least ( 1 + ( m - 1 )*abs( INCX ) ) otherwise. Before entry,
75 the incremented array X must contain the vector x. Unchanged on
76 exit.
77
78 INCX - INTEGER
79 On entry, INCX specifies the increment for the elements of X.
80 INCX must not be zero. Unchanged on exit.
81
82 BETA - REAL
83 On entry, BETA specifies the scalar beta. When BETA is supplied
84 as zero then Y need not be set on input. Unchanged on exit.
85
86 Y - REAL array of DIMENSION at least
87 ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n' and at
88 least ( 1 + ( n - 1 )*abs( INCY ) ) otherwise. Before entry
89 with BETA non-zero, the incremented array Y must contain the
90 vector y. On exit, Y is overwritten by the updated vector y.
91
92 INCY - INTEGER
93 On entry, INCY specifies the increment for the elements of Y.
94 INCY must not be zero. Unchanged on exit. Level 2 Blas rou‐
95 tine.
96
97
98
99 LAPACK routine (version 3.2) November 2008 SLA_GBAMV(1)