ZGERU performs the rank 1 operation A := alphaxy**T + A, where alpha is a scalar, x is an m element vector, y is an n element vector and A is an m by n matrix.
Type | Intent | Optional | Attributes | Name | ||
---|---|---|---|---|---|---|
integer(kind=ilp), | intent(in) | :: | m | |||
integer(kind=ilp), | intent(in) | :: | n | |||
complex(kind=dp), | intent(in) | :: | alpha | |||
complex(kind=dp), | intent(in) | :: | x(*) | |||
integer(kind=ilp), | intent(in) | :: | incx | |||
complex(kind=dp), | intent(in) | :: | y(*) | |||
integer(kind=ilp), | intent(in) | :: | incy | |||
complex(kind=dp), | intent(inout) | :: | a(lda,*) | |||
integer(kind=ilp), | intent(in) | :: | lda |
pure subroutine stdlib_zgeru(m,n,alpha,x,incx,y,incy,a,lda) !! ZGERU performs the rank 1 operation !! A := alpha*x*y**T + A, !! where alpha is a scalar, x is an m element vector, y is an n element !! vector and A is an m by n matrix. ! -- reference blas level2 routine -- ! -- reference blas is a software package provided by univ. of tennessee, -- ! -- univ. of california berkeley, univ. of colorado denver and nag ltd..-- ! Scalar Arguments complex(dp), intent(in) :: alpha integer(ilp), intent(in) :: incx, incy, lda, m, n ! Array Arguments complex(dp), intent(inout) :: a(lda,*) complex(dp), intent(in) :: x(*), y(*) ! ===================================================================== ! Local Scalars complex(dp) :: temp integer(ilp) :: i, info, ix, j, jy, kx ! Intrinsic Functions intrinsic :: max ! test the input parameters. info = 0 if (m<0) then info = 1 else if (n<0) then info = 2 else if (incx==0) then info = 5 else if (incy==0) then info = 7 else if (lda<max(1,m)) then info = 9 end if if (info/=0) then call stdlib_xerbla('ZGERU ',info) return end if ! quick return if possible. if ((m==0) .or. (n==0) .or. (alpha==czero)) return ! start the operations. in this version the elements of a are ! accessed sequentially with cone pass through a. if (incy>0) then jy = 1 else jy = 1 - (n-1)*incy end if if (incx==1) then do j = 1,n if (y(jy)/=czero) then temp = alpha*y(jy) do i = 1,m a(i,j) = a(i,j) + x(i)*temp end do end if jy = jy + incy end do else if (incx>0) then kx = 1 else kx = 1 - (m-1)*incx end if do j = 1,n if (y(jy)/=czero) then temp = alpha*y(jy) ix = kx do i = 1,m a(i,j) = a(i,j) + x(ix)*temp ix = ix + incx end do end if jy = jy + incy end do end if return end subroutine stdlib_zgeru