LAPACK 3.12.1
LAPACK: Linear Algebra PACKage
All Classes Namespaces Files Functions Variables Typedefs Enumerations Enumerator Macros Modules Pages

◆ zgerc()

subroutine zgerc ( integer m,
integer n,
complex*16 alpha,
complex*16, dimension(*) x,
integer incx,
complex*16, dimension(*) y,
integer incy,
complex*16, dimension(lda,*) a,
integer lda )

ZGERC

Purpose:
!> !> ZGERC performs the rank 1 operation !> !> A := alpha*x*y**H + 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. !>
Parameters
[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]X
!> X is COMPLEX*16 array, dimension at least !> ( 1 + ( m - 1 )*abs( INCX ) ). !> Before entry, the incremented array X must contain the m !> element vector x. !>
[in]INCX
!> INCX is INTEGER !> On entry, INCX specifies the increment for the elements of !> X. INCX must not be zero. !>
[in]Y
!> Y is COMPLEX*16 array, dimension at least !> ( 1 + ( n - 1 )*abs( INCY ) ). !> Before entry, the incremented array Y must contain the n !> element vector y. !>
[in]INCY
!> INCY is INTEGER !> On entry, INCY specifies the increment for the elements of !> Y. INCY must not be zero. !>
[in,out]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. On exit, A is !> overwritten by the updated matrix. !>
[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 ). !>
Author
Univ. of Tennessee
Univ. of California Berkeley
Univ. of Colorado Denver
NAG Ltd.
Further Details:
!> !> Level 2 Blas routine. !> !> -- 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 129 of file zgerc.f.

130*
131* -- Reference BLAS level2 routine --
132* -- Reference BLAS is a software package provided by Univ. of Tennessee, --
133* -- Univ. of California Berkeley, Univ. of Colorado Denver and NAG Ltd..--
134*
135* .. Scalar Arguments ..
136 COMPLEX*16 ALPHA
137 INTEGER INCX,INCY,LDA,M,N
138* ..
139* .. Array Arguments ..
140 COMPLEX*16 A(LDA,*),X(*),Y(*)
141* ..
142*
143* =====================================================================
144*
145* .. Parameters ..
146 COMPLEX*16 ZERO
147 parameter(zero= (0.0d+0,0.0d+0))
148* ..
149* .. Local Scalars ..
150 COMPLEX*16 TEMP
151 INTEGER I,INFO,IX,J,JY,KX
152* ..
153* .. External Subroutines ..
154 EXTERNAL xerbla
155* ..
156* .. Intrinsic Functions ..
157 INTRINSIC dconjg,max
158* ..
159*
160* Test the input parameters.
161*
162 info = 0
163 IF (m.LT.0) THEN
164 info = 1
165 ELSE IF (n.LT.0) THEN
166 info = 2
167 ELSE IF (incx.EQ.0) THEN
168 info = 5
169 ELSE IF (incy.EQ.0) THEN
170 info = 7
171 ELSE IF (lda.LT.max(1,m)) THEN
172 info = 9
173 END IF
174 IF (info.NE.0) THEN
175 CALL xerbla('ZGERC ',info)
176 RETURN
177 END IF
178*
179* Quick return if possible.
180*
181 IF ((m.EQ.0) .OR. (n.EQ.0) .OR. (alpha.EQ.zero)) RETURN
182*
183* Start the operations. In this version the elements of A are
184* accessed sequentially with one pass through A.
185*
186 IF (incy.GT.0) THEN
187 jy = 1
188 ELSE
189 jy = 1 - (n-1)*incy
190 END IF
191 IF (incx.EQ.1) THEN
192 DO 20 j = 1,n
193 IF (y(jy).NE.zero) THEN
194 temp = alpha*dconjg(y(jy))
195 DO 10 i = 1,m
196 a(i,j) = a(i,j) + x(i)*temp
197 10 CONTINUE
198 END IF
199 jy = jy + incy
200 20 CONTINUE
201 ELSE
202 IF (incx.GT.0) THEN
203 kx = 1
204 ELSE
205 kx = 1 - (m-1)*incx
206 END IF
207 DO 40 j = 1,n
208 IF (y(jy).NE.zero) THEN
209 temp = alpha*dconjg(y(jy))
210 ix = kx
211 DO 30 i = 1,m
212 a(i,j) = a(i,j) + x(ix)*temp
213 ix = ix + incx
214 30 CONTINUE
215 END IF
216 jy = jy + incy
217 40 CONTINUE
218 END IF
219*
220 RETURN
221*
222* End of ZGERC
223*
subroutine xerbla(srname, info)
Definition cblat2.f:3285
Here is the call graph for this function:
Here is the caller graph for this function: