KTH framework for Nek5000 toolboxes; testing version  0.0.1
dgemv.f
Go to the documentation of this file.
1  SUBROUTINE dgemv ( TRANS, M, N, ALPHA, A, LDA, X, INCX,
2  $ BETA, Y, INCY )
3 * .. Scalar Arguments ..
4  DOUBLE PRECISION ALPHA, BETA
5  INTEGER INCX, INCY, LDA, M, N
6  CHARACTER*1 TRANS
7 * .. Array Arguments ..
8  DOUBLE PRECISION A( LDA, * ), X( * ), Y( * )
9 * ..
10 *
11 * Purpose
12 * =======
13 *
14 * DGEMV performs one of the matrix-vector operations
15 *
16 * y := alpha*A*x + beta*y, or y := alpha*A'*x + beta*y,
17 *
18 * where alpha and beta are scalars, x and y are vectors and A is an
19 * m by n matrix.
20 *
21 * Parameters
22 * ==========
23 *
24 * TRANS - CHARACTER*1.
25 * On entry, TRANS specifies the operation to be performed as
26 * follows:
27 *
28 * TRANS = 'N' or 'n' y := alpha*A*x + beta*y.
29 *
30 * TRANS = 'T' or 't' y := alpha*A'*x + beta*y.
31 *
32 * TRANS = 'C' or 'c' y := alpha*A'*x + beta*y.
33 *
34 * Unchanged on exit.
35 *
36 * M - INTEGER.
37 * On entry, M specifies the number of rows of the matrix A.
38 * M must be at least zero.
39 * Unchanged on exit.
40 *
41 * N - INTEGER.
42 * On entry, N specifies the number of columns of the matrix A.
43 * N must be at least zero.
44 * Unchanged on exit.
45 *
46 * ALPHA - DOUBLE PRECISION.
47 * On entry, ALPHA specifies the scalar alpha.
48 * Unchanged on exit.
49 *
50 * A - DOUBLE PRECISION array of DIMENSION ( LDA, n ).
51 * Before entry, the leading m by n part of the array A must
52 * contain the matrix of coefficients.
53 * Unchanged on exit.
54 *
55 * LDA - INTEGER.
56 * On entry, LDA specifies the first dimension of A as declared
57 * in the calling (sub) program. LDA must be at least
58 * max( 1, m ).
59 * Unchanged on exit.
60 *
61 * X - DOUBLE PRECISION array of DIMENSION at least
62 * ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'
63 * and at least
64 * ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.
65 * Before entry, the incremented array X must contain the
66 * vector x.
67 * Unchanged on exit.
68 *
69 * INCX - INTEGER.
70 * On entry, INCX specifies the increment for the elements of
71 * X. INCX must not be zero.
72 * Unchanged on exit.
73 *
74 * BETA - DOUBLE PRECISION.
75 * On entry, BETA specifies the scalar beta. When BETA is
76 * supplied as zero then Y need not be set on input.
77 * Unchanged on exit.
78 *
79 * Y - DOUBLE PRECISION array of DIMENSION at least
80 * ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'
81 * and at least
82 * ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.
83 * Before entry with BETA non-zero, the incremented array Y
84 * must contain the vector y. On exit, Y is overwritten by the
85 * updated vector y.
86 *
87 * INCY - INTEGER.
88 * On entry, INCY specifies the increment for the elements of
89 * Y. INCY must not be zero.
90 * Unchanged on exit.
91 *
92 *
93 * Level 2 Blas routine.
94 *
95 * -- Written on 22-October-1986.
96 * Jack Dongarra, Argonne National Lab.
97 * Jeremy Du Croz, Nag Central Office.
98 * Sven Hammarling, Nag Central Office.
99 * Richard Hanson, Sandia National Labs.
100 *
101 *
102 * .. Parameters ..
103  DOUBLE PRECISION ONE , ZERO
104  parameter( one = 1.0d+0, zero = 0.0d+0 )
105 * .. Local Scalars ..
106  DOUBLE PRECISION TEMP
107  INTEGER I, INFO, IX, IY, J, JX, JY, KX, KY, LENX, LENY
108 * .. External Functions ..
109  LOGICAL LSAME
110  EXTERNAL lsame
111 * .. External Subroutines ..
112  EXTERNAL xerbla
113 * .. Intrinsic Functions ..
114  INTRINSIC max
115 * ..
116 * .. Executable Statements ..
117 *
118 * Test the input parameters.
119 *
120  info = 0
121  IF ( .NOT.lsame( trans, 'N' ).AND.
122  $ .NOT.lsame( trans, 'T' ).AND.
123  $ .NOT.lsame( trans, 'C' ) )THEN
124  info = 1
125  ELSE IF( m.LT.0 )THEN
126  info = 2
127  ELSE IF( n.LT.0 )THEN
128  info = 3
129  ELSE IF( lda.LT.max( 1, m ) )THEN
130  info = 6
131  ELSE IF( incx.EQ.0 )THEN
132  info = 8
133  ELSE IF( incy.EQ.0 )THEN
134  info = 11
135  END IF
136  IF( info.NE.0 )THEN
137  CALL xerbla( 'DGEMV ', info )
138  RETURN
139  END IF
140 *
141 * Quick return if possible.
142 *
143  IF( ( m.EQ.0 ).OR.( n.EQ.0 ).OR.
144  $ ( ( alpha.EQ.zero ).AND.( beta.EQ.one ) ) )
145  $ RETURN
146 *
147 * Set LENX and LENY, the lengths of the vectors x and y, and set
148 * up the start points in X and Y.
149 *
150  IF( lsame( trans, 'N' ) )THEN
151  lenx = n
152  leny = m
153  ELSE
154  lenx = m
155  leny = n
156  END IF
157  IF( incx.GT.0 )THEN
158  kx = 1
159  ELSE
160  kx = 1 - ( lenx - 1 )*incx
161  END IF
162  IF( incy.GT.0 )THEN
163  ky = 1
164  ELSE
165  ky = 1 - ( leny - 1 )*incy
166  END IF
167 *
168 * Start the operations. In this version the elements of A are
169 * accessed sequentially with one pass through A.
170 *
171 * First form y := beta*y.
172 *
173  IF( beta.NE.one )THEN
174  IF( incy.EQ.1 )THEN
175  IF( beta.EQ.zero )THEN
176  DO 10, i = 1, leny
177  y( i ) = zero
178  10 CONTINUE
179  ELSE
180  DO 20, i = 1, leny
181  y( i ) = beta*y( i )
182  20 CONTINUE
183  END IF
184  ELSE
185  iy = ky
186  IF( beta.EQ.zero )THEN
187  DO 30, i = 1, leny
188  y( iy ) = zero
189  iy = iy + incy
190  30 CONTINUE
191  ELSE
192  DO 40, i = 1, leny
193  y( iy ) = beta*y( iy )
194  iy = iy + incy
195  40 CONTINUE
196  END IF
197  END IF
198  END IF
199  IF( alpha.EQ.zero )
200  $ RETURN
201  IF( lsame( trans, 'N' ) )THEN
202 *
203 * Form y := alpha*A*x + y.
204 *
205  jx = kx
206  IF( incy.EQ.1 )THEN
207  DO 60, j = 1, n
208  IF( x( jx ).NE.zero )THEN
209  temp = alpha*x( jx )
210  DO 50, i = 1, m
211  y( i ) = y( i ) + temp*a( i, j )
212  50 CONTINUE
213  END IF
214  jx = jx + incx
215  60 CONTINUE
216  ELSE
217  DO 80, j = 1, n
218  IF( x( jx ).NE.zero )THEN
219  temp = alpha*x( jx )
220  iy = ky
221  DO 70, i = 1, m
222  y( iy ) = y( iy ) + temp*a( i, j )
223  iy = iy + incy
224  70 CONTINUE
225  END IF
226  jx = jx + incx
227  80 CONTINUE
228  END IF
229  ELSE
230 *
231 * Form y := alpha*A'*x + y.
232 *
233  jy = ky
234  IF( incx.EQ.1 )THEN
235  DO 100, j = 1, n
236  temp = zero
237  DO 90, i = 1, m
238  temp = temp + a( i, j )*x( i )
239  90 CONTINUE
240  y( jy ) = y( jy ) + alpha*temp
241  jy = jy + incy
242  100 CONTINUE
243  ELSE
244  DO 120, j = 1, n
245  temp = zero
246  ix = kx
247  DO 110, i = 1, m
248  temp = temp + a( i, j )*x( ix )
249  ix = ix + incx
250  110 CONTINUE
251  y( jy ) = y( jy ) + alpha*temp
252  jy = jy + incy
253  120 CONTINUE
254  END IF
255  END IF
256 *
257  RETURN
258 *
259 * End of DGEMV .
260 *
261  END
subroutine dgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
Definition: dgemv.f:3
subroutine xerbla(SRNAME, INFO)
Definition: xerbla.f:2