Contents


NAME

     zcnvcor2 - compute the convolution or correlation of complex
     matrices

SYNOPSIS

     SUBROUTINE ZCNVCOR2(CNVCOR, METHOD, TRANSX, SCRATCHX, TRANSY,
           SCRATCHY, MX, NX, X, LDX, MY, NY, MPRE, NPRE, Y, LDY, MZ, NZ, Z,
           LDZ, WORKIN, LWORK)

     CHARACTER * 1  CNVCOR,  METHOD,  TRANSX,  SCRATCHX,  TRANSY,
     SCRATCHY
     DOUBLE COMPLEX X(LDX,*), Y(LDY,*), Z(LDZ,*), WORKIN(*)
     INTEGER MX, NX, LDX, MY, NY, MPRE, NPRE, LDY, MZ,  NZ,  LDZ,
     LWORK

     SUBROUTINE ZCNVCOR2_64(CNVCOR, METHOD, TRANSX, SCRATCHX, TRANSY,
           SCRATCHY, MX, NX, X, LDX, MY, NY, MPRE, NPRE, Y, LDY, MZ, NZ, Z,
           LDZ, WORKIN, LWORK)

     CHARACTER * 1  CNVCOR,  METHOD,  TRANSX,  SCRATCHX,  TRANSY,
     SCRATCHY
     DOUBLE COMPLEX X(LDX,*), Y(LDY,*), Z(LDZ,*), WORKIN(*)
     INTEGER*8 MX, NX, LDX, MY, NY, MPRE, NPRE, LDY, MZ, NZ, LDZ,
     LWORK

  F95 INTERFACE
     SUBROUTINE CNVCOR2(CNVCOR, METHOD, TRANSX, SCRATCHX, TRANSY,
            SCRATCHY, [MX], [NX], X, [LDX], [MY], [NY], MPRE, NPRE, Y, [LDY],
            [MZ], [NZ], Z, [LDZ], WORKIN, [LWORK])

     CHARACTER(LEN=1)  ::  CNVCOR,  METHOD,   TRANSX,   SCRATCHX,
     TRANSY, SCRATCHY
     COMPLEX(8), DIMENSION(:) :: WORKIN
     COMPLEX(8), DIMENSION(:,:) :: X, Y, Z
     INTEGER :: MX, NX, LDX, MY, NY, MPRE,  NPRE,  LDY,  MZ,  NZ,
     LDZ, LWORK

     SUBROUTINE CNVCOR2_64(CNVCOR, METHOD, TRANSX, SCRATCHX, TRANSY,
            SCRATCHY, [MX], [NX], X, [LDX], [MY], [NY], MPRE, NPRE, Y, [LDY],
            [MZ], [NZ], Z, [LDZ], WORKIN, [LWORK])

     CHARACTER(LEN=1)  ::  CNVCOR,  METHOD,   TRANSX,   SCRATCHX,
     TRANSY, SCRATCHY
     COMPLEX(8), DIMENSION(:) :: WORKIN
     COMPLEX(8), DIMENSION(:,:) :: X, Y, Z
     INTEGER(8) :: MX, NX, LDX, MY, NY, MPRE, NPRE, LDY, MZ,  NZ,
     LDZ, LWORK
  C INTERFACE
     #include <sunperf.h>

     void zcnvcor2(char cnvcor, char method,  char  transx,  char
               scratchx,  char transy, char scratchy, int mx, int
               nx, doublecomplex *x, int ldx, int my, int ny, int
               mpre, int npre, doublecomplex *y, int ldy, int mz,
               int nz, doublecomplex *z, int  ldz,  doublecomplex
               *workin, int lwork);

     void zcnvcor2_64(char cnvcor, char method, char transx, char
               scratchx,  char  transy,  char  scratchy, long mx,
               long nx, doublecomplex *x, long ldx, long my, long
               ny,  long  mpre, long npre, doublecomplex *y, long
               ldy, long mz, long nz, doublecomplex *z, long ldz,
               doublecomplex *workin, long lwork);

PURPOSE

     zcnvcor2 computes the convolution or correlation of  complex
     matrices.

ARGUMENTS

     CNVCOR (input)
               'V' or 'v' to compute convolution, 'R' or  'r'  to
               compute correlation.

     METHOD (input)
               'T' or 't' if the Fourier transform method  is  to
               be  used,  'D' or 'd' to compute directly from the
               definition.

     TRANSX (input)
               'N' or 'n' if X is the filter matrix, 'T'  or  't'
               if transpose(X) is the filter matrix.

     SCRATCHX (input)
               'N' or 'n' if X must be preserved, 'S' or 's' if X
               can  be  used as scratch space.  The contents of X
               are undefined after returning from a call in which
               X is allowed to be used for scratch.

     TRANSY (input)
               'N' or 'n' if Y is the input matrix, 'T' or 't' if
               transpose(Y) is the input matrix.
     SCRATCHY (input)
               'N' or 'n' if Y must be preserved, 'S' or 's' if Y
               can  be  used as scratch space.  The contents of Y
               are undefined after returning from a call in which
               Y is allowed to be used for scratch.

     MX (input)
               Number of rows in the filter matrix.  MX >= 0.

     NX (input)
               Number of columns in the filter matrix.  NX >= 0.

     X (input)  dimension(LDX,NX)
               On entry, the filter matrix.  Unchanged on exit if
               SCRATCHX  is  'N'  or  'n',  undefined  on exit if
               SCRATCHX is 'S' or 's'.

     LDX (input)
               Leading dimension of the array that  contains  the
               filter matrix.

     MY (input)
               Number of rows in the input matrix.  MY >= 0.

     NY (input)
               Number of columns in the input matrix.  NY >= 0.

     MPRE (input)
               Number of implicit zeros to prepend to each row of
               the input matrix.  MPRE >= 0.

     NPRE (input)
               Number of implicit zeros to prepend to each column
               of the input matrix.  NPRE >= 0.

     Y (input)  dimension(LDY,*)
               Input matrix.  Unchanged on exit  if  SCRATCHY  is
               'N'  or  'n', undefined on exit if SCRATCHY is 'S'
               or 's'.

     LDY (input)
               Leading dimension of the array that  contains  the
               input matrix.

     MZ (input)
               Number of rows in the output  matrix.   MZ  >=  0.
               ZCNVCOR2 will return immediately if MZ = 0.

     NZ (input)
               Number of columns in the output matrix.  NZ >=  0.
               ZCNVCOR2 will return immediately if NZ = 0.

     Z (output)
                dimension(LDZ,*)
               Result matrix.

     LDZ (input)
               Leading dimension of the array that  contains  the
               result matrix.  LDZ >= MAX(1,MZ).

     WORKIN (input/output)
               (input/scratch) dimension(LWORK)
               On entry for the first call to ZCNVCOR2, WORKIN(1)
               must  contain  CMPLX(0.0,0.0).   After  the  first
               call, WORKIN(1) must be set to CMPLX(0.0,0.0)  iff
               WORKIN  has  been  altered  since the last call to
               this subroutine or if the sizes of the arrays have
               changed.

     LWORK (input)
               Length of the work vector.  If the FFT  is  to  be
               used  then for best performance LWORK should be at
               least 30 words longer than the  amount  of  memory
               needed to hold the trig tables.  If the FFT is not
               used, the value of LWORK is unimportant.