LAPACK 3.11.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches
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, 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, 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, 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*> \ingroup complex_blas_level2
140*
141*> \par Further Details:
142* =====================
143*>
144*> \verbatim
145*>
146*> Level 2 Blas routine.
147*> The vector and matrix arguments are not referenced when N = 0, or M = 0
148*>
149*> -- Written on 22-October-1986.
150*> Jack Dongarra, Argonne National Lab.
151*> Jeremy Du Croz, Nag Central Office.
152*> Sven Hammarling, Nag Central Office.
153*> Richard Hanson, Sandia National Labs.
154*> \endverbatim
155*>
156* =====================================================================
157 SUBROUTINE cgemv(TRANS,M,N,ALPHA,A,LDA,X,INCX,BETA,Y,INCY)
158*
159* -- Reference BLAS level2 routine --
160* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
161* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
162*
163* .. Scalar Arguments ..
164 COMPLEX ALPHA,BETA
165 INTEGER INCX,INCY,LDA,M,N
166 CHARACTER TRANS
167* ..
168* .. Array Arguments ..
169 COMPLEX A(LDA,*),X(*),Y(*)
170* ..
171*
172* =====================================================================
173*
174* .. Parameters ..
175 COMPLEX ONE
176 parameter(one= (1.0e+0,0.0e+0))
177 COMPLEX ZERO
178 parameter(zero= (0.0e+0,0.0e+0))
179* ..
180* .. Local Scalars ..
181 COMPLEX TEMP
182 INTEGER I,INFO,IX,IY,J,JX,JY,KX,KY,LENX,LENY
183 LOGICAL NOCONJ
184* ..
185* .. External Functions ..
186 LOGICAL LSAME
187 EXTERNAL lsame
188* ..
189* .. External Subroutines ..
190 EXTERNAL xerbla
191* ..
192* .. Intrinsic Functions ..
193 INTRINSIC conjg,max
194* ..
195*
196* Test the input parameters.
197*
198 info = 0
199 IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
200 + .NOT.lsame(trans,'C')) THEN
201 info = 1
202 ELSE IF (m.LT.0) THEN
203 info = 2
204 ELSE IF (n.LT.0) THEN
205 info = 3
206 ELSE IF (lda.LT.max(1,m)) THEN
207 info = 6
208 ELSE IF (incx.EQ.0) THEN
209 info = 8
210 ELSE IF (incy.EQ.0) THEN
211 info = 11
212 END IF
213 IF (info.NE.0) THEN
214 CALL xerbla('CGEMV ',info)
215 RETURN
216 END IF
217*
218* Quick return if possible.
219*
220 IF ((m.EQ.0) .OR. (n.EQ.0) .OR.
221 + ((alpha.EQ.zero).AND. (beta.EQ.one))) RETURN
222*
223 noconj = lsame(trans,'T')
224*
225* Set LENX and LENY, the lengths of the vectors x and y, and set
226* up the start points in X and Y.
227*
228 IF (lsame(trans,'N')) THEN
229 lenx = n
230 leny = m
231 ELSE
232 lenx = m
233 leny = n
234 END IF
235 IF (incx.GT.0) THEN
236 kx = 1
237 ELSE
238 kx = 1 - (lenx-1)*incx
239 END IF
240 IF (incy.GT.0) THEN
241 ky = 1
242 ELSE
243 ky = 1 - (leny-1)*incy
244 END IF
245*
246* Start the operations. In this version the elements of A are
247* accessed sequentially with one pass through A.
248*
249* First form y := beta*y.
250*
251 IF (beta.NE.one) THEN
252 IF (incy.EQ.1) THEN
253 IF (beta.EQ.zero) THEN
254 DO 10 i = 1,leny
255 y(i) = zero
256 10 CONTINUE
257 ELSE
258 DO 20 i = 1,leny
259 y(i) = beta*y(i)
260 20 CONTINUE
261 END IF
262 ELSE
263 iy = ky
264 IF (beta.EQ.zero) THEN
265 DO 30 i = 1,leny
266 y(iy) = zero
267 iy = iy + incy
268 30 CONTINUE
269 ELSE
270 DO 40 i = 1,leny
271 y(iy) = beta*y(iy)
272 iy = iy + incy
273 40 CONTINUE
274 END IF
275 END IF
276 END IF
277 IF (alpha.EQ.zero) RETURN
278 IF (lsame(trans,'N')) THEN
279*
280* Form y := alpha*A*x + y.
281*
282 jx = kx
283 IF (incy.EQ.1) THEN
284 DO 60 j = 1,n
285 temp = alpha*x(jx)
286 DO 50 i = 1,m
287 y(i) = y(i) + temp*a(i,j)
288 50 CONTINUE
289 jx = jx + incx
290 60 CONTINUE
291 ELSE
292 DO 80 j = 1,n
293 temp = alpha*x(jx)
294 iy = ky
295 DO 70 i = 1,m
296 y(iy) = y(iy) + temp*a(i,j)
297 iy = iy + incy
298 70 CONTINUE
299 jx = jx + incx
300 80 CONTINUE
301 END IF
302 ELSE
303*
304* Form y := alpha*A**T*x + y or y := alpha*A**H*x + y.
305*
306 jy = ky
307 IF (incx.EQ.1) THEN
308 DO 110 j = 1,n
309 temp = zero
310 IF (noconj) THEN
311 DO 90 i = 1,m
312 temp = temp + a(i,j)*x(i)
313 90 CONTINUE
314 ELSE
315 DO 100 i = 1,m
316 temp = temp + conjg(a(i,j))*x(i)
317 100 CONTINUE
318 END IF
319 y(jy) = y(jy) + alpha*temp
320 jy = jy + incy
321 110 CONTINUE
322 ELSE
323 DO 140 j = 1,n
324 temp = zero
325 ix = kx
326 IF (noconj) THEN
327 DO 120 i = 1,m
328 temp = temp + a(i,j)*x(ix)
329 ix = ix + incx
330 120 CONTINUE
331 ELSE
332 DO 130 i = 1,m
333 temp = temp + conjg(a(i,j))*x(ix)
334 ix = ix + incx
335 130 CONTINUE
336 END IF
337 y(jy) = y(jy) + alpha*temp
338 jy = jy + incy
339 140 CONTINUE
340 END IF
341 END IF
342*
343 RETURN
344*
345* End of CGEMV
346*
347 END
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
subroutine cgemv(TRANS, M, N, ALPHA, A, LDA, X, INCX, BETA, Y, INCY)
CGEMV
Definition: cgemv.f:158