Contents


NAME

     ccnvcor - compute the convolution or correlation of  complex
     vectors

SYNOPSIS

     SUBROUTINE CCNVCOR(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
     COMPLEX X(*), Y(*), Z(*), WORK(*)
     INTEGER NX, IFX, INCX, NY, NPRE, M, IFY, INC1Y,  INC2Y,  NZ,
     K, IFZ, INC1Z, INC2Z, LWORK

     SUBROUTINE CCNVCOR_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
     COMPLEX X(*), Y(*), Z(*), WORK(*)
     INTEGER*8 NX, IFX, INCX, NY, NPRE, M, IFY, INC1Y, INC2Y, NZ,
     K, IFZ, INC1Z, INC2Z, LWORK

  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
     COMPLEX, DIMENSION(:) :: X, Y, Z, WORK
     INTEGER :: NX, IFX, INCX, NY, NPRE, M,  IFY,  INC1Y,  INC2Y,
     NZ, K, IFZ, INC1Z, INC2Z, LWORK

     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
     COMPLEX, DIMENSION(:) :: X, Y, Z, WORK
     INTEGER(8) :: NX, IFX, INCX, NY, NPRE, M, IFY, INC1Y, INC2Y,
     NZ, K, IFZ, INC1Z, INC2Z, LWORK

  C INTERFACE
     #include <sunperf.h>

     void ccnvcor(char cnvcor, char four, int nx, complex *x, int
               ifx,  int  incx,  int ny, int npre, int m, complex
               *y, int ify, int inc1y, int inc2y, int nz, int  k,
               complex *z, int ifz, int inc1z, int inc2z, complex
               *work, int lwork);
     void ccnvcor_64(char cnvcor, char four, long nx, complex *x,
               long  ifx,  long incx, long ny, long npre, long m,
               complex *y, long ify, long inc1y, long inc2y, long
               nz, long k, complex *z, long ifz, long inc1z, long
               inc2z, complex *work, long lwork);

PURPOSE

     ccnvcor computes the convolution or correlation  of  complex
     vectors.

ARGUMENTS

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

     FOUR (input)
                CHARACTER
               '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 real and imaginary parts of
               the filter and data vectors  consist  entirely  of
               integers  or  vectors where elements of either the
               filter vector or a given data vector differ signi-
               ficantly  in magnitude from the 1-norm of the vec-
               tor.

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

     X (input)  dimension(*)
               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.   CCNVCOR
               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.   CCNVCOR  will
               return immediately if M = 0.

     Y (input)  dimension(*)
               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.   CCNVCOR
               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
               CCNVCOR  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)
                dimension(*)
               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)
               (input/scratch) dimension(LWORK)
               Scratch space.  Before the first call  to  CCNVCOR
               with  particular  values  of the integer arguments
               the first element of WORK must be set to zero.  If
               WORK  is  written  between  calls to CCNVCOR or if
               CCNVCOR 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 CCNVCOR
               run faster.

     LWORK (input)
               Length of WORK.  LWORK >= 2*MAX(NX,NY+NPRE,NZ)+8.