LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
cgemv.f
Go to the documentation of this file.
1 *> \brief \b CGEMV
2 *
3 * =========== DOCUMENTATION ===========
4 *
5 * Online html documentation available at
6 * http://www.netlib.org/lapack/explore-html/
7 *
8 * Definition:
9 * ===========
10 *
11 * SUBROUTINE CGEMV(TRANS,M,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
12 *
13 * .. Scalar Arguments ..
14 * COMPLEX ALPHA,BETA
15 * INTEGER INCX,INCY,LDA,M,N
16 * CHARACTER TRANS
17 * ..
18 * .. Array Arguments ..
19 * COMPLEX A(LDA,*),X(*),Y(*)
20 * ..
21 *
22 *
23 *> \par Purpose:
24 * =============
25 *>
26 *> \verbatim
27 *>
28 *> CGEMV performs one of the matrix-vector operations
29 *>
30 *> y := alpha*A*x + beta*y, or y := alpha*A**T*x + beta*y, or
31 *>
32 *> y := alpha*A**H*x + beta*y,
33 *>
34 *> where alpha and beta are scalars, x and y are vectors and A is an
35 *> m by n matrix.
36 *> \endverbatim
37 *
38 * Arguments:
39 * ==========
40 *
41 *> \param[in] TRANS
42 *> \verbatim
43 *> TRANS is CHARACTER*1
44 *> On entry, TRANS specifies the operation to be performed as
45 *> follows:
46 *>
47 *> TRANS = 'N' or 'n' y := alpha*A*x + beta*y.
48 *>
49 *> TRANS = 'T' or 't' y := alpha*A**T*x + beta*y.
50 *>
51 *> TRANS = 'C' or 'c' y := alpha*A**H*x + beta*y.
52 *> \endverbatim
53 *>
54 *> \param[in] M
55 *> \verbatim
56 *> M is INTEGER
57 *> On entry, M specifies the number of rows of the matrix A.
58 *> M must be at least zero.
59 *> \endverbatim
60 *>
61 *> \param[in] N
62 *> \verbatim
63 *> N is INTEGER
64 *> On entry, N specifies the number of columns of the matrix A.
65 *> N must be at least zero.
66 *> \endverbatim
67 *>
68 *> \param[in] ALPHA
69 *> \verbatim
70 *> ALPHA is COMPLEX
71 *> On entry, ALPHA specifies the scalar alpha.
72 *> \endverbatim
73 *>
74 *> \param[in] A
75 *> \verbatim
76 *> A is COMPLEX array of DIMENSION ( LDA, n ).
77 *> Before entry, the leading m by n part of the array A must
78 *> contain the matrix of coefficients.
79 *> \endverbatim
80 *>
81 *> \param[in] LDA
82 *> \verbatim
83 *> LDA is INTEGER
84 *> On entry, LDA specifies the first dimension of A as declared
85 *> in the calling (sub) program. LDA must be at least
86 *> max( 1, m ).
87 *> \endverbatim
88 *>
89 *> \param[in] X
90 *> \verbatim
91 *> X is COMPLEX array of DIMENSION at least
92 *> ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'
93 *> and at least
94 *> ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.
95 *> Before entry, the incremented array X must contain the
96 *> vector x.
97 *> \endverbatim
98 *>
99 *> \param[in] INCX
100 *> \verbatim
101 *> INCX is INTEGER
102 *> On entry, INCX specifies the increment for the elements of
103 *> X. INCX must not be zero.
104 *> \endverbatim
105 *>
106 *> \param[in] BETA
107 *> \verbatim
108 *> BETA is COMPLEX
109 *> On entry, BETA specifies the scalar beta. When BETA is
110 *> supplied as zero then Y need not be set on input.
111 *> \endverbatim
112 *>
113 *> \param[in,out] Y
114 *> \verbatim
115 *> Y is COMPLEX array of DIMENSION at least
116 *> ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'
117 *> and at least
118 *> ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.
119 *> Before entry with BETA non-zero, the incremented array Y
120 *> must contain the vector y. On exit, Y is overwritten by the
121 *> updated vector y.
122 *> \endverbatim
123 *>
124 *> \param[in] INCY
125 *> \verbatim
126 *> INCY is INTEGER
127 *> On entry, INCY specifies the increment for the elements of
128 *> Y. INCY must not be zero.
129 *> \endverbatim
130 *
131 * Authors:
132 * ========
133 *
134 *> \author Univ. of Tennessee
135 *> \author Univ. of California Berkeley
136 *> \author Univ. of Colorado Denver
137 *> \author NAG Ltd.
138 *
139 *> \date November 2015
140 *
141 *> \ingroup complex_blas_level2
142 *
143 *> \par Further Details:
144 * =====================
145 *>
146 *> \verbatim
147 *>
148 *> Level 2 Blas routine.
149 *> The vector and matrix arguments are not referenced when N = 0, or M = 0
150 *>
151 *> -- Written on 22-October-1986.
152 *> Jack Dongarra, Argonne National Lab.
153 *> Jeremy Du Croz, Nag Central Office.
154 *> Sven Hammarling, Nag Central Office.
155 *> Richard Hanson, Sandia National Labs.
156 *> \endverbatim
157 *>
158 * =====================================================================
159  SUBROUTINE cgemv(TRANS,M,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
160 *
161 * -- Reference BLAS level2 routine (version 3.6.0) --
162 * -- Reference BLAS is a software package provided by Univ. of Tennessee, --
163 * -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
164 * November 2015
165 *
166 * .. Scalar Arguments ..
167  COMPLEX ALPHA,BETA
168  INTEGER INCX,INCY,LDA,M,N
169  CHARACTER TRANS
170 * ..
171 * .. Array Arguments ..
172  COMPLEX A(lda,*),X(*),Y(*)
173 * ..
174 *
175 * =====================================================================
176 *
177 * .. Parameters ..
178  COMPLEX ONE
179  parameter(one= (1.0e+0,0.0e+0))
180  COMPLEX ZERO
181  parameter(zero= (0.0e+0,0.0e+0))
182 * ..
183 * .. Local Scalars ..
184  COMPLEX TEMP
185  INTEGER I,INFO,IX,IY,J,JX,JY,KX,KY,LENX,LENY
186  LOGICAL NOCONJ
187 * ..
188 * .. External Functions ..
189  LOGICAL LSAME
190  EXTERNAL lsame
191 * ..
192 * .. External Subroutines ..
193  EXTERNAL xerbla
194 * ..
195 * .. Intrinsic Functions ..
196  INTRINSIC conjg,max
197 * ..
198 *
199 * Test the input parameters.
200 *
201  info = 0
202  IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
203  + .NOT.lsame(trans,'C')) THEN
204  info = 1
205  ELSE IF (m.LT.0) THEN
206  info = 2
207  ELSE IF (n.LT.0) THEN
208  info = 3
209  ELSE IF (lda.LT.max(1,m)) THEN
210  info = 6
211  ELSE IF (incx.EQ.0) THEN
212  info = 8
213  ELSE IF (incy.EQ.0) THEN
214  info = 11
215  END IF
216  IF (info.NE.0) THEN
217  CALL xerbla('CGEMV ',info)
218  RETURN
219  END IF
220 *
221 * Quick return if possible.
222 *
223  IF ((m.EQ.0) .OR. (n.EQ.0) .OR.
224  + ((alpha.EQ.zero).AND. (beta.EQ.one))) RETURN
225 *
226  noconj = lsame(trans,'T')
227 *
228 * Set LENX and LENY, the lengths of the vectors x and y, and set
229 * up the start points in X and Y.
230 *
231  IF (lsame(trans,'N')) THEN
232  lenx = n
233  leny = m
234  ELSE
235  lenx = m
236  leny = n
237  END IF
238  IF (incx.GT.0) THEN
239  kx = 1
240  ELSE
241  kx = 1 - (lenx-1)*incx
242  END IF
243  IF (incy.GT.0) THEN
244  ky = 1
245  ELSE
246  ky = 1 - (leny-1)*incy
247  END IF
248 *
249 * Start the operations. In this version the elements of A are
250 * accessed sequentially with one pass through A.
251 *
252 * First form y := beta*y.
253 *
254  IF (beta.NE.one) THEN
255  IF (incy.EQ.1) THEN
256  IF (beta.EQ.zero) THEN
257  DO 10 i = 1,leny
258  y(i) = zero
259  10 CONTINUE
260  ELSE
261  DO 20 i = 1,leny
262  y(i) = beta*y(i)
263  20 CONTINUE
264  END IF
265  ELSE
266  iy = ky
267  IF (beta.EQ.zero) THEN
268  DO 30 i = 1,leny
269  y(iy) = zero
270  iy = iy + incy
271  30 CONTINUE
272  ELSE
273  DO 40 i = 1,leny
274  y(iy) = beta*y(iy)
275  iy = iy + incy
276  40 CONTINUE
277  END IF
278  END IF
279  END IF
280  IF (alpha.EQ.zero) RETURN
281  IF (lsame(trans,'N')) THEN
282 *
283 * Form y := alpha*A*x + y.
284 *
285  jx = kx
286  IF (incy.EQ.1) THEN
287  DO 60 j = 1,n
288  temp = alpha*x(jx)
289  DO 50 i = 1,m
290  y(i) = y(i) + temp*a(i,j)
291  50 CONTINUE
292  jx = jx + incx
293  60 CONTINUE
294  ELSE
295  DO 80 j = 1,n
296  temp = alpha*x(jx)
297  iy = ky
298  DO 70 i = 1,m
299  y(iy) = y(iy) + temp*a(i,j)
300  iy = iy + incy
301  70 CONTINUE
302  jx = jx + incx
303  80 CONTINUE
304  END IF
305  ELSE
306 *
307 * Form y := alpha*A**T*x + y or y := alpha*A**H*x + y.
308 *
309  jy = ky
310  IF (incx.EQ.1) THEN
311  DO 110 j = 1,n
312  temp = zero
313  IF (noconj) THEN
314  DO 90 i = 1,m
315  temp = temp + a(i,j)*x(i)
316  90 CONTINUE
317  ELSE
318  DO 100 i = 1,m
319  temp = temp + conjg(a(i,j))*x(i)
320  100 CONTINUE
321  END IF
322  y(jy) = y(jy) + alpha*temp
323  jy = jy + incy
324  110 CONTINUE
325  ELSE
326  DO 140 j = 1,n
327  temp = zero
328  ix = kx
329  IF (noconj) THEN
330  DO 120 i = 1,m
331  temp = temp + a(i,j)*x(ix)
332  ix = ix + incx
333  120 CONTINUE
334  ELSE
335  DO 130 i = 1,m
336  temp = temp + conjg(a(i,j))*x(ix)
337  ix = ix + incx
338  130 CONTINUE
339  END IF
340  y(jy) = y(jy) + alpha*temp
341  jy = jy + incy
342  140 CONTINUE
343  END IF
344  END IF
345 *
346  RETURN
347 *
348 * End of CGEMV .
349 *
350  END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
subroutine cgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
CGEMV
Definition: cgemv.f:160