LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
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 of 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 of 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 of 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.
Date
November 2015
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 160 of file cgemv.f.

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 *
subroutine xerbla(SRNAME, INFO)
XERBLA
Definition: xerbla.f:62
logical function lsame(CA, CB)
LSAME
Definition: lsame.f:55

Here is the call graph for this function: