LAPACK  3.6.1
LAPACK: Linear Algebra PACKage
subroutine cgeru ( integer  M,
integer  N,
complex  ALPHA,
complex, dimension(*)  X,
integer  INCX,
complex, dimension(*)  Y,
integer  INCY,
complex, dimension(lda,*)  A,
integer  LDA 
)

CGERU

Purpose:
 CGERU  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.
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
           On entry, ALPHA specifies the scalar alpha.
[in]X
          X is COMPLEX array of 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 array of 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 array of 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.
Date
November 2011
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 132 of file cgeru.f.

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

Here is the call graph for this function:

Here is the caller graph for this function: