Contents


NAME

     dcnvcor - compute the convolution  or  correlation  of  real
     vectors

SYNOPSIS

     SUBROUTINE DCNVCOR(CNVCOR, FOUR, NX, X, IFX, INCX, NY, NPRE, M, Y,
           IFY, INC1Y, INC2Y, NZ, K, Z, IFZ, INC1Z, INC2Z, WORK, LWORK)

     CHARACTER * 1 CNVCOR, FOUR
     INTEGER NX, IFX, INCX, NY, NPRE, M, IFY, INC1Y,  INC2Y,  NZ,
     K, IFZ, INC1Z, INC2Z, LWORK
     DOUBLE PRECISION X(*), Y(*), Z(*), WORK(*)

     SUBROUTINE DCNVCOR_64(CNVCOR, FOUR, NX, X, IFX, INCX, NY, NPRE, M, Y,
           IFY, INC1Y, INC2Y, NZ, K, Z, IFZ, INC1Z, INC2Z, WORK, LWORK)

     CHARACTER * 1 CNVCOR, FOUR
     INTEGER*8 NX, IFX, INCX, NY, NPRE, M, IFY, INC1Y, INC2Y, NZ,
     K, IFZ, INC1Z, INC2Z, LWORK
     DOUBLE PRECISION X(*), Y(*), Z(*), WORK(*)

  F95 INTERFACE
     SUBROUTINE CNVCOR(CNVCOR, FOUR, [NX], X, IFX, [INCX], NY, NPRE, M, Y,
            IFY, INC1Y, INC2Y, NZ, K, Z, IFZ, INC1Z, INC2Z, WORK, [LWORK])

     CHARACTER(LEN=1) :: CNVCOR, FOUR
     INTEGER :: NX, IFX, INCX, NY, NPRE, M,  IFY,  INC1Y,  INC2Y,
     NZ, K, IFZ, INC1Z, INC2Z, LWORK
     REAL(8), DIMENSION(:) :: X, Y, Z, WORK

     SUBROUTINE CNVCOR_64(CNVCOR, FOUR, [NX], X, IFX, [INCX], NY, NPRE, M,
            Y, IFY, INC1Y, INC2Y, NZ, K, Z, IFZ, INC1Z, INC2Z, WORK, [LWORK])

     CHARACTER(LEN=1) :: CNVCOR, FOUR
     INTEGER(8) :: NX, IFX, INCX, NY, NPRE, M, IFY, INC1Y, INC2Y,
     NZ, K, IFZ, INC1Z, INC2Z, LWORK
     REAL(8), DIMENSION(:) :: X, Y, Z, WORK

  C INTERFACE
     #include <sunperf.h>

     void dcnvcor(char cnvcor, char four, int nx, double *x,  int
               ifx, int incx, int ny, int npre, int m, double *y,
               int ify, int inc1y, int inc2y, int nz, int k, dou-
               ble  *z,  int  ifz,  int  inc1z, int inc2z, double
               *work, int lwork);
     void dcnvcor_64(char cnvcor, char four, long nx, double  *x,
               long  ifx,  long incx, long ny, long npre, long m,
               double *y, long ify, long inc1y, long inc2y,  long
               nz,  long k, double *z, long ifz, long inc1z, long
               inc2z, double *work, long lwork);

PURPOSE

     dcnvcor computes the convolution or correlation of real vec-
     tors.

ARGUMENTS

     CNVCOR (input)
               'V' or 'v' if convolution is desired, 'R'  or  'r'
               if correlation is desired.

     FOUR (input)
               'T' or 't' if the Fourier transform method  is  to
               be  used,  'D' or 'd' if the computation should be
               done directly from the  definition.   The  Fourier
               transform  method  is generally faster, but it may
               introduce noticeable errors into certain  results,
               notably when both the filter and data vectors con-
               sist entirely of integers or  vectors  where  ele-
               ments  of either the filter vector or a given data
               vector differ significantly in magnitude from  the
               1-norm of the vector.

     NX (input)
               Length of the filter vector.  NX  >=  0.   DCNVCOR
               will return immediately if NX = 0.

     X (input)
               Filter vector.

     IFX (input)
               Index of the first element of X.  NX >= IFX >= 1.

     INCX (input)
               Stride between elements of the filter vector in X.
               INCX > 0.

     NY (input)
               Length of the input vectors.  NY  >=  0.   DCNVCOR
               will return immediately if NY = 0.
     NPRE (input)
               The number of implicit zeros prepended  to  the  Y
               vectors.  NPRE >= 0.

     M (input)
               Number of input vectors.  M >=  0.   DCNVCOR  will
               return immediately if M = 0.

     Y (input)
               Input vectors.

     IFY (input)
               Index of the first element of Y.  NY >= IFY >= 1.

     INC1Y (input)
               Stride between elements of the input vectors in Y.
               INC1Y > 0.

     INC2Y (input)
               Stride between the input vectors in Y.  INC2Y > 0.

     NZ (input)
               Length of the output vectors.  NZ >=  0.   DCNVCOR
               will  return immediately if NZ = 0.  See the Notes
               section below for information about how this argu-
               ment  interacts with NX and NY to control circular
               versus end-off shifting.

     K (input)
               Number of Z vectors.  K >=  0.   If  K  =  0  then
               DCNVCOR  will  return  immediately.  If K < M then
               only the first K input vectors will be  processed.
               If K > M then M input vectors will be processed.

     Z (output)
               Result vectors.

     IFZ (input)
               Index of the first element of Z.  NZ >= IFZ >= 1.

     INC1Z (input)
               Stride between elements of the output  vectors  in
               Z.  INC1Z > 0.

     INC2Z (input)
               Stride between the output vectors in Z.   INC2Z  >
               0.

     WORK (input/output)
               Scratch space.  Before the first call  to  DCNVCOR
               with  particular  values  of the integer arguments
               the first element of WORK must be set to zero.  If
               WORK  is  written  between  calls to DCNVCOR or if
               DCNVCOR is called with  different  values  of  the
               integer  arguments  then the first element of WORK
               must again be set to zero before  each  call.   If
               WORK  has  not been written and the same values of
               the integer arguments are used then the first ele-
               ment of WORK to zero.  This can avoid certain ini-
               tializations that store their results  into  WORK,
               and  avoiding  the initialization can make DCNVCOR
               run faster.

     LWORK (input)
               Length of WORK.  LWORK >= 4*MAX(NX,NY,NZ)+15.

NOTES

     If any vector overlaps a writable vector, either because  of
     argument  aliasing  or  ill-chosen values of the various INC
     arguments, the results are undefined and may vary  from  one
     run to the next.

     The most common form of the computation, and the  case  that
     executes  fastest, is applying a filter vector X to a series
     of vectors stored in the columns of Y with the result placed
     into  the  columns of Z.  In that case, INCX = 1, INC1Y = 1,
     INC2Y >= NY, INC1Z = 1, INC2Z >= NZ.  Another common form is
     applying  a filter vector X to a series of vectors stored in
     the rows of Y and store the result in the row of Z, in which
     case  INCX  =  1,  INC1Y  >= NY, INC2Y = 1, INC1Z >= NZ, and
     INC2Z = 1.