Contents


NAME

     rfft2f - compute the  Fourier  coefficients  of  a  periodic
     sequence.   The  RFFT operations are unnormalized, so a call
     of RFFT2F followed by a call of  RFFT2B  will  multiply  the
     input sequence by M*N.

SYNOPSIS

     SUBROUTINE RFFT2F(PLACE, FULL, M, N, A, LDA, B, LDB, WORK, LWORK)

     CHARACTER * 1 PLACE, FULL
     INTEGER M, N, LDA, LDB, LWORK
     REAL A(LDA,*), B(LDB,*), WORK(*)

     SUBROUTINE RFFT2F_64(PLACE, FULL, M, N, A, LDA, B, LDB, WORK, LWORK)

     CHARACTER * 1 PLACE, FULL
     INTEGER*8 M, N, LDA, LDB, LWORK
     REAL A(LDA,*), B(LDB,*), WORK(*)

  F95 INTERFACE
     SUBROUTINE FFT2F(PLACE, FULL, [M], [N], A, [LDA], B, [LDB], WORK,
            LWORK)

     CHARACTER(LEN=1) :: PLACE, FULL
     INTEGER :: M, N, LDA, LDB, LWORK
     REAL, DIMENSION(:) :: WORK
     REAL, DIMENSION(:,:) :: A, B

     SUBROUTINE FFT2F_64(PLACE, FULL, [M], [N], A, [LDA], B, [LDB], WORK,
            LWORK)

     CHARACTER(LEN=1) :: PLACE, FULL
     INTEGER(8) :: M, N, LDA, LDB, LWORK
     REAL, DIMENSION(:) :: WORK
     REAL, DIMENSION(:,:) :: A, B

  C INTERFACE
     #include <sunperf.h>

     void rfft2f(char place, char full, int m, int n,  float  *a,
               int  lda,  float  *b,  int  ldb,  float *work, int
               lwork);

     void rfft2f_64(char place, char full, long m, long n,  float
               *a,  long  lda,  float  *b, long ldb, float *work,
               long lwork);

ARGUMENTS

     PLACE (input)
               Character.  If PLACE = 'I' or 'i' (for in-place) ,
               the  input  and output data are stored in array A.
               If PLACE = 'O'  or  'o'  (for  out-of-place),  the
               input  data  is stored in array B while the output
               is stored in A.

     FULL (input)
               Indicates whether or  not  to  generate  the  full
               result  matrix.   'F'  or 'f' will cause RFFT2F to
               generate the full result matrix.  Otherwise only a
               partial  matrix  that  takes advantage of symmetry
               will be generated.

     M (input) Integer  specifying  the  number  of  rows  to  be
               transformed.   It  is  most  efficient when M is a
               product of small primes.  M >= 0; when M = 0,  the
               subroutine  returns  immediately  without changing
               any data.

     N (input) Integer specifying the number  of  columns  to  be
               transformed.   It is most most efficient when N is
               a product of small primes.  N >= 0; when  N  =  0,
               the  subroutine returns immediately without chang-
               ing any data.

     A (input/output)
               On entry, a two-dimensional  array  A(LDA,N)  that
               contains the data to be transformed.  Upon exit, A
               is unchanged if an out-of-place transform is done.
               If  an  in-place  transform with partial result is
               requested,  A(1:(M/2+1)*2,1:N)  will  contain  the
               transformed  results.   If  an  in-place transform
               with full result is requested,  A(1:2*M,1:N)  will
               contain complete transformed results.

     LDA (input)
               Leading dimension of the array containing the data
               to  be  transformed.   LDA  must  be  even  if the
               transformed sequences are to be stored in A.
               If PLACE = ('O' or 'o') LDA >= M
               If PLACE = ('I' or 'i') LDA must be even.  If
               FULL = ('F' or 'f'), LDA >= 2*M
               FULL is not ('F' or 'f'), LDA >= (M/2+1)*2
     B (input/output)
               Upon exit, a two-dimensional array B(2*LDB,N) that
               contains  the  transformed  results  if an out-of-
               place transform is  done.   Otherwise,  B  is  not
               used.
               If an out-of-place transform is done and  FULL  is
               not  'F'  or  'f', B(1:(M/2+1)*2,1:N) will contain
               the partial transformed results.  If FULL = 'F' or
               'f',   B(1:2*M,1:N)   will  contain  the  complete
               transformed results.

     LDB (input)
               2*LDB is the leading dimension of the array B.  If
               an in-place transform is desired LDB is ignored.
               If PLACE is ('O' or 'o') and
               FULL is ('F' or 'f'), LDB >= M
               FULL is not ('F' or 'f'), LDB >= M/2+1
               Note that even though LDB is used in the  argument
               list, 2*LDB is the actual leading dimension of B.

     WORK (input/output)
               One-dimensional real  array  of  length  at  least
               LWORK.   On input, WORK must have been initialized
               by RFFT2I.

     LWORK (input)
               Integer.  LWORK >= (M + 2*N + MAX(M, 2*N) + 30)