-- Do not edit! Automatically generated by fftw-generate.
module Numeric.FFTW.FFI.Function where

import Numeric.FFTW.FFI.Type (Plan, IODim, Sign, Flags, Kind)

import qualified Foreign.C.Types as C
import Foreign.Ptr (Ptr)

import Data.Complex (Complex)


type PlanDFT1d a =
   C.CInt ->
   Ptr (Complex a) -> Ptr (Complex a) ->
   Sign -> Flags -> IO (Plan a)

type PlanDFT2d a =
   C.CInt -> C.CInt ->
   Ptr (Complex a) -> Ptr (Complex a) ->
   Sign -> Flags -> IO (Plan a)

type PlanDFT3d a =
   C.CInt -> C.CInt -> C.CInt ->
   Ptr (Complex a) -> Ptr (Complex a) ->
   Sign -> Flags -> IO (Plan a)

type PlanDFT a =
   C.CInt -> Ptr C.CInt ->
   Ptr (Complex a) -> Ptr (Complex a) ->
   Sign -> Flags -> IO (Plan a)

type PlanDFTr2c1d a =
   C.CInt ->
   Ptr a -> Ptr (Complex a) ->
   Flags -> IO (Plan a)

type PlanDFTr2c2d a =
   C.CInt -> C.CInt ->
   Ptr a -> Ptr (Complex a) ->
   Flags -> IO (Plan a)

type PlanDFTr2c3d a =
   C.CInt -> C.CInt -> C.CInt ->
   Ptr a -> Ptr (Complex a) ->
   Flags -> IO (Plan a)

type PlanDFTr2c a =
   C.CInt -> Ptr C.CInt ->
   Ptr a -> Ptr (Complex a) ->
   Flags -> IO (Plan a)

type PlanDFTc2r1d a =
   C.CInt ->
   Ptr (Complex a) -> Ptr a ->
   Flags -> IO (Plan a)

type PlanDFTc2r2d a =
   C.CInt -> C.CInt ->
   Ptr (Complex a) -> Ptr a ->
   Flags -> IO (Plan a)

type PlanDFTc2r3d a =
   C.CInt -> C.CInt -> C.CInt ->
   Ptr (Complex a) -> Ptr a ->
   Flags -> IO (Plan a)

type PlanDFTc2r a =
   C.CInt -> Ptr C.CInt ->
   Ptr (Complex a) -> Ptr a ->
   Flags -> IO (Plan a)

type PlanR2r1d a =
   C.CInt ->
   Ptr a -> Ptr a ->
   Kind -> Flags -> IO (Plan a)

type PlanR2r2d a =
   C.CInt -> C.CInt ->
   Ptr a -> Ptr a ->
   Kind -> Kind -> Flags -> IO (Plan a)

type PlanR2r3d a =
   C.CInt -> C.CInt -> C.CInt ->
   Ptr a -> Ptr a ->
   Kind -> Kind -> Kind -> Flags -> IO (Plan a)

type PlanR2r a =
   C.CInt -> Ptr C.CInt ->
   Ptr a -> Ptr a ->
   Ptr Kind -> Flags -> IO (Plan a)

type PlanManyDFT a =
   C.CInt -> Ptr C.CInt -> C.CInt ->
   Ptr (Complex a) -> Ptr C.CInt ->
   C.CInt -> C.CInt ->
   Ptr (Complex a) -> Ptr C.CInt ->
   C.CInt -> C.CInt ->
   Sign -> Flags -> IO (Plan a)

type PlanManyDFTr2c a =
   C.CInt -> Ptr C.CInt -> C.CInt ->
   Ptr a -> Ptr C.CInt ->
   C.CInt -> C.CInt ->
   Ptr (Complex a) -> Ptr C.CInt ->
   C.CInt -> C.CInt ->
   Flags -> IO (Plan a)

type PlanManyDFTc2r a =
   C.CInt -> Ptr C.CInt -> C.CInt ->
   Ptr (Complex a) -> Ptr C.CInt ->
   C.CInt -> C.CInt ->
   Ptr a -> Ptr C.CInt ->
   C.CInt -> C.CInt ->
   Flags -> IO (Plan a)

type PlanManyR2r a =
   C.CInt -> Ptr C.CInt -> C.CInt ->
   Ptr a -> Ptr C.CInt ->
   C.CInt -> C.CInt ->
   Ptr a -> Ptr C.CInt ->
   C.CInt -> C.CInt ->
   Ptr Kind -> Flags -> IO (Plan a)

type PlanGuruDFT a =
   C.CInt -> Ptr IODim -> C.CInt -> Ptr IODim ->
   Ptr (Complex a) -> Ptr (Complex a) -> Sign -> Flags -> IO (Plan a)

type PlanGuruDFTr2c a =
   C.CInt -> Ptr IODim -> C.CInt -> Ptr IODim ->
   Ptr a -> Ptr (Complex a) -> Flags -> IO (Plan a)

type PlanGuruDFTc2r a =
   C.CInt -> Ptr IODim -> C.CInt -> Ptr IODim ->
   Ptr (Complex a) -> Ptr a -> Flags -> IO (Plan a)

type PlanGuruR2r a =
   C.CInt -> Ptr IODim -> C.CInt -> Ptr IODim ->
   Ptr a -> Ptr a -> Ptr Kind -> Flags -> IO (Plan a)

type PlanGuruSplitDFT a =
   C.CInt -> Ptr IODim -> C.CInt -> Ptr IODim ->
   Ptr a -> Ptr a -> Ptr a -> Ptr a -> Flags -> IO (Plan a)

type PlanGuruSplitDFTr2c a =
   C.CInt -> Ptr IODim -> C.CInt -> Ptr IODim ->
   Ptr a -> Ptr a -> Ptr a -> Flags -> IO (Plan a)

type PlanGuruSplitDFTc2r a =
   C.CInt -> Ptr IODim -> C.CInt -> Ptr IODim ->
   Ptr a -> Ptr a -> Ptr a -> Flags -> IO (Plan a)

type DestroyPlan a =
   Plan a -> IO ()

type Execute a =
   Plan a -> IO ()

type ExecuteDFT a =
   Plan a -> Ptr (Complex a) -> Ptr (Complex a) -> IO ()

type ExecuteDFTr2c a =
   Plan a -> Ptr a -> Ptr (Complex a) -> IO ()

type ExecuteDFTc2r a =
   Plan a -> Ptr (Complex a) -> Ptr a -> IO ()

type ExecuteR2r a =
   Plan a -> Ptr a -> Ptr a -> IO ()

type ExecuteSplitDFT a =
   Plan a -> Ptr a -> Ptr a -> Ptr a -> Ptr a -> IO ()

type ExecuteSplitDFTr2c a =
   Plan a -> Ptr a -> Ptr a -> Ptr a -> IO ()

type ExecuteSplitDFTc2r a =
   Plan a -> Ptr a -> Ptr a -> Ptr a -> IO ()

type Malloc a =
   C.CSize -> IO (Ptr a)

type Free a =
   Ptr a -> IO ()

type AllocReal a =
   C.CSize -> IO (Ptr a)

type AllocComplex a =
   C.CSize -> IO (Ptr (Complex a))

type FreeComplex a =
   Ptr (Complex a) -> IO ()