Go to main content
Oracle Developer Studio 12.5 Man Pages

Exit Print View

Updated: June 2017
 
 

dger (3p)

Name

dger - perform the rank 1 operation A := alpha*x*y' + A

Synopsis

SUBROUTINE DGER(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)

INTEGER M, N, INCX, INCY, LDA
DOUBLE PRECISION ALPHA
DOUBLE PRECISION X(*), Y(*), A(LDA,*)

SUBROUTINE DGER_64(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)

INTEGER*8 M, N, INCX, INCY, LDA
DOUBLE PRECISION ALPHA
DOUBLE PRECISION X(*), Y(*), A(LDA,*)




F95 INTERFACE
SUBROUTINE GER(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)

INTEGER :: M, N, INCX, INCY, LDA
REAL(8) :: ALPHA
REAL(8), DIMENSION(:) :: X, Y
REAL(8), DIMENSION(:,:) :: A

SUBROUTINE GER_64(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)

INTEGER(8) :: M, N, INCX, INCY, LDA
REAL(8) :: ALPHA
REAL(8), DIMENSION(:) :: X, Y
REAL(8), DIMENSION(:,:) :: A




C INTERFACE
#include <sunperf.h>

void  dger(int  m, int n, double alpha, double *x, int incx, double *y,
int incy, double *a, int lda);

void dger_64(long m, long n, double alpha, double *x, long incx, double
*y, long incy, double *a, long lda);

Description

Oracle Solaris Studio Performance Library                             dger(3P)



NAME
       dger - perform the rank 1 operation   A := alpha*x*y' + A


SYNOPSIS
       SUBROUTINE DGER(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)

       INTEGER M, N, INCX, INCY, LDA
       DOUBLE PRECISION ALPHA
       DOUBLE PRECISION X(*), Y(*), A(LDA,*)

       SUBROUTINE DGER_64(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)

       INTEGER*8 M, N, INCX, INCY, LDA
       DOUBLE PRECISION ALPHA
       DOUBLE PRECISION X(*), Y(*), A(LDA,*)




   F95 INTERFACE
       SUBROUTINE GER(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)

       INTEGER :: M, N, INCX, INCY, LDA
       REAL(8) :: ALPHA
       REAL(8), DIMENSION(:) :: X, Y
       REAL(8), DIMENSION(:,:) :: A

       SUBROUTINE GER_64(M, N, ALPHA, X, INCX, Y, INCY, A, LDA)

       INTEGER(8) :: M, N, INCX, INCY, LDA
       REAL(8) :: ALPHA
       REAL(8), DIMENSION(:) :: X, Y
       REAL(8), DIMENSION(:,:) :: A




   C INTERFACE
       #include <sunperf.h>

       void  dger(int  m, int n, double alpha, double *x, int incx, double *y,
                 int incy, double *a, int lda);

       void dger_64(long m, long n, double alpha, double *x, long incx, double
                 *y, long incy, double *a, long lda);



PURPOSE
       dger  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 (input)
                 On  entry, M specifies the number of rows of the matrix A.  M
                 >= 0.  Unchanged on exit.


       N (input)
                 On entry, N specifies the number of columns of the matrix  A.
                 N >= 0.  Unchanged on exit.


       ALPHA (input)
                 On  entry,  ALPHA  specifies  the scalar alpha.  Unchanged on
                 exit.


       X (input)
                 ( 1 + ( m - 1 )*abs( INCX ) ).  Before entry, the incremented
                 array  X  must  contain the m element vector x.  Unchanged on
                 exit.


       INCX (input)
                 On entry, INCX specifies the increment for the elements of X.
                 INCX <> 0.  Unchanged on exit.


       Y (input)
                 ( 1 + ( n - 1 )*abs( INCY ) ).  Before entry, the incremented
                 array Y must contain the n element vector  y.   Unchanged  on
                 exit.


       INCY (input)
                 On entry, INCY specifies the increment for the elements of Y.
                 INCY <> 0.  Unchanged on exit.


       A (input/output)
                 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 (input)
                 On entry, LDA specifies the first dimension of A as  declared
                 in  the calling (sub) program. LDA >= max( 1, m ).  Unchanged
                 on exit.




                                  7 Nov 2015                          dger(3P)