summaryrefslogtreecommitdiff
path: root/BLAS/SRC/zgeru.f
diff options
context:
space:
mode:
authorjason <jason@8a072113-8704-0410-8d35-dd094bca7971>2008-10-28 01:38:50 +0000
committerjason <jason@8a072113-8704-0410-8d35-dd094bca7971>2008-10-28 01:38:50 +0000
commitbaba851215b44ac3b60b9248eb02bcce7eb76247 (patch)
tree8c0f5c006875532a30d4409f5e94b0f310ff00a7 /BLAS/SRC/zgeru.f
downloadlapack-baba851215b44ac3b60b9248eb02bcce7eb76247.tar.gz
lapack-baba851215b44ac3b60b9248eb02bcce7eb76247.tar.bz2
lapack-baba851215b44ac3b60b9248eb02bcce7eb76247.zip
Move LAPACK trunk into position.
Diffstat (limited to 'BLAS/SRC/zgeru.f')
-rw-r--r--BLAS/SRC/zgeru.f159
1 files changed, 159 insertions, 0 deletions
diff --git a/BLAS/SRC/zgeru.f b/BLAS/SRC/zgeru.f
new file mode 100644
index 00000000..4293a1c2
--- /dev/null
+++ b/BLAS/SRC/zgeru.f
@@ -0,0 +1,159 @@
+ SUBROUTINE ZGERU(M,N,ALPHA,X,INCX,Y,INCY,A,LDA)
+* .. Scalar Arguments ..
+ DOUBLE COMPLEX ALPHA
+ INTEGER INCX,INCY,LDA,M,N
+* ..
+* .. Array Arguments ..
+ DOUBLE COMPLEX A(LDA,*),X(*),Y(*)
+* ..
+*
+* Purpose
+* =======
+*
+* ZGERU performs the rank 1 operation
+*
+* A := alpha*x*y' + 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.
+*
+* Arguments
+* ==========
+*
+* M - INTEGER.
+* On entry, M specifies the number of rows of the matrix A.
+* M must be at least zero.
+* Unchanged on exit.
+*
+* N - INTEGER.
+* On entry, N specifies the number of columns of the matrix A.
+* N must be at least zero.
+* Unchanged on exit.
+*
+* ALPHA - COMPLEX*16 .
+* On entry, ALPHA specifies the scalar alpha.
+* Unchanged on exit.
+*
+* X - COMPLEX*16 array of dimension at least
+* ( 1 + ( m - 1 )*abs( INCX ) ).
+* Before entry, the incremented array X must contain the m
+* element vector x.
+* Unchanged on exit.
+*
+* INCX - INTEGER.
+* On entry, INCX specifies the increment for the elements of
+* X. INCX must not be zero.
+* Unchanged on exit.
+*
+* Y - COMPLEX*16 array of dimension at least
+* ( 1 + ( n - 1 )*abs( INCY ) ).
+* Before entry, the incremented array Y must contain the n
+* element vector y.
+* Unchanged on exit.
+*
+* INCY - INTEGER.
+* On entry, INCY specifies the increment for the elements of
+* Y. INCY must not be zero.
+* Unchanged on exit.
+*
+* A - COMPLEX*16 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.
+*
+* LDA - 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 ).
+* Unchanged on exit.
+*
+*
+* 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.
+*
+*
+* .. Parameters ..
+ DOUBLE COMPLEX ZERO
+ PARAMETER (ZERO= (0.0D+0,0.0D+0))
+* ..
+* .. Local Scalars ..
+ DOUBLE COMPLEX TEMP
+ INTEGER I,INFO,IX,J,JY,KX
+* ..
+* .. External Subroutines ..
+ EXTERNAL XERBLA
+* ..
+* .. Intrinsic Functions ..
+ INTRINSIC MAX
+* ..
+*
+* Test the input parameters.
+*
+ INFO = 0
+ IF (M.LT.0) THEN
+ INFO = 1
+ ELSE IF (N.LT.0) THEN
+ INFO = 2
+ ELSE IF (INCX.EQ.0) THEN
+ INFO = 5
+ ELSE IF (INCY.EQ.0) THEN
+ INFO = 7
+ ELSE IF (LDA.LT.MAX(1,M)) THEN
+ INFO = 9
+ END IF
+ IF (INFO.NE.0) THEN
+ CALL XERBLA('ZGERU ',INFO)
+ RETURN
+ END IF
+*
+* Quick return if possible.
+*
+ IF ((M.EQ.0) .OR. (N.EQ.0) .OR. (ALPHA.EQ.ZERO)) RETURN
+*
+* Start the operations. In this version the elements of A are
+* accessed sequentially with one pass through A.
+*
+ IF (INCY.GT.0) THEN
+ JY = 1
+ ELSE
+ JY = 1 - (N-1)*INCY
+ END IF
+ IF (INCX.EQ.1) THEN
+ DO 20 J = 1,N
+ IF (Y(JY).NE.ZERO) THEN
+ TEMP = ALPHA*Y(JY)
+ DO 10 I = 1,M
+ A(I,J) = A(I,J) + X(I)*TEMP
+ 10 CONTINUE
+ END IF
+ JY = JY + INCY
+ 20 CONTINUE
+ ELSE
+ IF (INCX.GT.0) THEN
+ KX = 1
+ ELSE
+ KX = 1 - (M-1)*INCX
+ END IF
+ DO 40 J = 1,N
+ IF (Y(JY).NE.ZERO) THEN
+ TEMP = ALPHA*Y(JY)
+ IX = KX
+ DO 30 I = 1,M
+ A(I,J) = A(I,J) + X(IX)*TEMP
+ IX = IX + INCX
+ 30 CONTINUE
+ END IF
+ JY = JY + INCY
+ 40 CONTINUE
+ END IF
+*
+ RETURN
+*
+* End of ZGERU .
+*
+ END