LAPACK 3.11.0
LAPACK: Linear Algebra PACKage
Loading...
Searching...
No Matches

◆ cgemv()

subroutine cgemv ( character  TRANS,
integer  M,
integer  N,
complex  ALPHA,
complex, dimension(lda,*)  A,
integer  LDA,
complex, dimension(*)  X,
integer  INCX,
complex  BETA,
complex, dimension(*)  Y,
integer  INCY 
)

CGEMV

Purpose:
 CGEMV performs one of the matrix-vector operations

    y := alpha*A*x + beta*y,   or   y := alpha*A**T*x + beta*y,   or

    y := alpha*A**H*x + beta*y,

 where alpha and beta are scalars, x and y are vectors and A is an
 m by n matrix.
Parameters
[in]TRANS
          TRANS is CHARACTER*1
           On entry, TRANS specifies the operation to be performed as
           follows:

              TRANS = 'N' or 'n'   y := alpha*A*x + beta*y.

              TRANS = 'T' or 't'   y := alpha*A**T*x + beta*y.

              TRANS = 'C' or 'c'   y := alpha*A**H*x + beta*y.
[in]M
          M is INTEGER
           On entry, M specifies the number of rows of the matrix A.
           M must be at least zero.
[in]N
          N is INTEGER
           On entry, N specifies the number of columns of the matrix A.
           N must be at least zero.
[in]ALPHA
          ALPHA is COMPLEX
           On entry, ALPHA specifies the scalar alpha.
[in]A
          A is COMPLEX array, dimension ( LDA, N )
           Before entry, the leading m by n part of the array A must
           contain the matrix of coefficients.
[in]LDA
          LDA is INTEGER
           On entry, LDA specifies the first dimension of A as declared
           in the calling (sub) program. LDA must be at least
           max( 1, m ).
[in]X
          X is COMPLEX array, dimension at least
           ( 1 + ( n - 1 )*abs( INCX ) ) when TRANS = 'N' or 'n'
           and at least
           ( 1 + ( m - 1 )*abs( INCX ) ) otherwise.
           Before entry, the incremented array X must contain the
           vector x.
[in]INCX
          INCX is INTEGER
           On entry, INCX specifies the increment for the elements of
           X. INCX must not be zero.
[in]BETA
          BETA is COMPLEX
           On entry, BETA specifies the scalar beta. When BETA is
           supplied as zero then Y need not be set on input.
[in,out]Y
          Y is COMPLEX array, dimension at least
           ( 1 + ( m - 1 )*abs( INCY ) ) when TRANS = 'N' or 'n'
           and at least
           ( 1 + ( n - 1 )*abs( INCY ) ) otherwise.
           Before entry with BETA non-zero, the incremented array Y
           must contain the vector y. On exit, Y is overwritten by the
           updated vector y.
[in]INCY
          INCY is INTEGER
           On entry, INCY specifies the increment for the elements of
           Y. INCY must not be zero.
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
  Level 2 Blas routine.
  The vector and matrix arguments are not referenced when N = 0, or M = 0

  -- Written on 22-October-1986.
     Jack Dongarra, Argonne National Lab.
     Jeremy Du Croz, Nag Central Office.
     Sven Hammarling, Nag Central Office.
     Richard Hanson, Sandia National Labs.

Definition at line 157 of file cgemv.f.

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*
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:60
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:53
Here is the call graph for this function: