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

◆ zgemv()

subroutine zgemv ( character trans,
integer m,
integer n,
complex*16 alpha,
complex*16, dimension(lda,*) a,
integer lda,
complex*16, dimension(*) x,
integer incx,
complex*16 beta,
complex*16, dimension(*) y,
integer incy )

ZGEMV

Purpose:
!>
!> ZGEMV  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*16
!>           On entry, ALPHA specifies the scalar alpha.
!> 
[in]A
!>          A is COMPLEX*16 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*16 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*16
!>           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*16 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.
!>           If either m or n is zero, then Y not referenced and the function
!>           performs a quick return.
!> 
[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 159 of file zgemv.f.

160*
161* -- Reference BLAS level2 routine --
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*
165* .. Scalar Arguments ..
166 COMPLEX*16 ALPHA,BETA
167 INTEGER INCX,INCY,LDA,M,N
168 CHARACTER TRANS
169* ..
170* .. Array Arguments ..
171 COMPLEX*16 A(LDA,*),X(*),Y(*)
172* ..
173*
174* =====================================================================
175*
176* .. Parameters ..
177 COMPLEX*16 ONE
178 parameter(one= (1.0d+0,0.0d+0))
179 COMPLEX*16 ZERO
180 parameter(zero= (0.0d+0,0.0d+0))
181* ..
182* .. Local Scalars ..
183 COMPLEX*16 TEMP
184 INTEGER I,INFO,IX,IY,J,JX,JY,KX,KY,LENX,LENY
185 LOGICAL NOCONJ
186* ..
187* .. External Functions ..
188 LOGICAL LSAME
189 EXTERNAL lsame
190* ..
191* .. External Subroutines ..
192 EXTERNAL xerbla
193* ..
194* .. Intrinsic Functions ..
195 INTRINSIC dconjg,max
196* ..
197*
198* Test the input parameters.
199*
200 info = 0
201 IF (.NOT.lsame(trans,'N') .AND. .NOT.lsame(trans,'T') .AND.
202 + .NOT.lsame(trans,'C')) THEN
203 info = 1
204 ELSE IF (m.LT.0) THEN
205 info = 2
206 ELSE IF (n.LT.0) THEN
207 info = 3
208 ELSE IF (lda.LT.max(1,m)) THEN
209 info = 6
210 ELSE IF (incx.EQ.0) THEN
211 info = 8
212 ELSE IF (incy.EQ.0) THEN
213 info = 11
214 END IF
215 IF (info.NE.0) THEN
216 CALL xerbla('ZGEMV ',info)
217 RETURN
218 END IF
219*
220* Quick return if possible.
221*
222 IF ((m.EQ.0) .OR. (n.EQ.0) .OR.
223 + ((alpha.EQ.zero).AND. (beta.EQ.one))) RETURN
224*
225 noconj = lsame(trans,'T')
226*
227* Set LENX and LENY, the lengths of the vectors x and y, and set
228* up the start points in X and Y.
229*
230 IF (lsame(trans,'N')) THEN
231 lenx = n
232 leny = m
233 ELSE
234 lenx = m
235 leny = n
236 END IF
237 IF (incx.GT.0) THEN
238 kx = 1
239 ELSE
240 kx = 1 - (lenx-1)*incx
241 END IF
242 IF (incy.GT.0) THEN
243 ky = 1
244 ELSE
245 ky = 1 - (leny-1)*incy
246 END IF
247*
248* Start the operations. In this version the elements of A are
249* accessed sequentially with one pass through A.
250*
251* First form y := beta*y.
252*
253 IF (beta.NE.one) THEN
254 IF (incy.EQ.1) THEN
255 IF (beta.EQ.zero) THEN
256 DO 10 i = 1,leny
257 y(i) = zero
258 10 CONTINUE
259 ELSE
260 DO 20 i = 1,leny
261 y(i) = beta*y(i)
262 20 CONTINUE
263 END IF
264 ELSE
265 iy = ky
266 IF (beta.EQ.zero) THEN
267 DO 30 i = 1,leny
268 y(iy) = zero
269 iy = iy + incy
270 30 CONTINUE
271 ELSE
272 DO 40 i = 1,leny
273 y(iy) = beta*y(iy)
274 iy = iy + incy
275 40 CONTINUE
276 END IF
277 END IF
278 END IF
279 IF (alpha.EQ.zero) RETURN
280 IF (lsame(trans,'N')) THEN
281*
282* Form y := alpha*A*x + y.
283*
284 jx = kx
285 IF (incy.EQ.1) THEN
286 DO 60 j = 1,n
287 temp = alpha*x(jx)
288 DO 50 i = 1,m
289 y(i) = y(i) + temp*a(i,j)
290 50 CONTINUE
291 jx = jx + incx
292 60 CONTINUE
293 ELSE
294 DO 80 j = 1,n
295 temp = alpha*x(jx)
296 iy = ky
297 DO 70 i = 1,m
298 y(iy) = y(iy) + temp*a(i,j)
299 iy = iy + incy
300 70 CONTINUE
301 jx = jx + incx
302 80 CONTINUE
303 END IF
304 ELSE
305*
306* Form y := alpha*A**T*x + y or y := alpha*A**H*x + y.
307*
308 jy = ky
309 IF (incx.EQ.1) THEN
310 DO 110 j = 1,n
311 temp = zero
312 IF (noconj) THEN
313 DO 90 i = 1,m
314 temp = temp + a(i,j)*x(i)
315 90 CONTINUE
316 ELSE
317 DO 100 i = 1,m
318 temp = temp + dconjg(a(i,j))*x(i)
319 100 CONTINUE
320 END IF
321 y(jy) = y(jy) + alpha*temp
322 jy = jy + incy
323 110 CONTINUE
324 ELSE
325 DO 140 j = 1,n
326 temp = zero
327 ix = kx
328 IF (noconj) THEN
329 DO 120 i = 1,m
330 temp = temp + a(i,j)*x(ix)
331 ix = ix + incx
332 120 CONTINUE
333 ELSE
334 DO 130 i = 1,m
335 temp = temp + dconjg(a(i,j))*x(ix)
336 ix = ix + incx
337 130 CONTINUE
338 END IF
339 y(jy) = y(jy) + alpha*temp
340 jy = jy + incy
341 140 CONTINUE
342 END IF
343 END IF
344*
345 RETURN
346*
347* End of ZGEMV
348*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
logical function lsame(ca, cb)
LSAME
Definition lsame.f:48
Here is the call graph for this function:
Here is the caller graph for this function: