comfort-fftw-0.0.0.1: High-level interface to FFTW (Fast Fourier Transform) based on comfort-array

Safe HaskellNone
LanguageHaskell98

Numeric.FFTW.Shape

Synopsis

Documentation

newtype Half n Source #

Constructors

Half n 
Instances
Eq n => Eq (Half n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

(==) :: Half n -> Half n -> Bool #

(/=) :: Half n -> Half n -> Bool #

Show n => Show (Half n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

showsPrec :: Int -> Half n -> ShowS #

show :: Half n -> String #

showList :: [Half n] -> ShowS #

Integral n => C (Half n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

size :: Half n -> Int #

Integral n => Indexed (Half n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Associated Types

type Index (Half n) :: Type #

Methods

indices :: Half n -> [Index (Half n)] #

offset :: Half n -> Index (Half n) -> Int #

uncheckedOffset :: Half n -> Index (Half n) -> Int #

unifiedOffset :: Checking check => Half n -> Index (Half n) -> Result check Int #

inBounds :: Half n -> Index (Half n) -> Bool #

sizeOffset :: Half n -> (Int, Index (Half n) -> Int) #

uncheckedSizeOffset :: Half n -> (Int, Index (Half n) -> Int) #

unifiedSizeOffset :: Checking check => Half n -> (Int, Index (Half n) -> Result check Int) #

Integral n => InvIndexed (Half n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

indexFromOffset :: Half n -> Int -> Index (Half n) #

uncheckedIndexFromOffset :: Half n -> Int -> Index (Half n) #

unifiedIndexFromOffset :: Checking check => Half n -> Int -> Result check (Index (Half n)) #

NFData n => NFData (Half n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

rnf :: Half n -> () #

type Index (Half n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

type Index (Half n) = n

class C sh => MultiCyclic sh where Source #

Methods

cyclicDimensions :: sh -> [CInt] Source #

Instances
MultiCyclic () Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

cyclicDimensions :: () -> [CInt] Source #

Integral n => MultiCyclic (Cyclic n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

(MultiCyclic sh0, MultiCyclic sh1) => MultiCyclic (sh0, sh1) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

cyclicDimensions :: (sh0, sh1) -> [CInt] Source #

(MultiCyclic sh0, MultiCyclic sh1, MultiCyclic sh2) => MultiCyclic (sh0, sh1, sh2) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

cyclicDimensions :: (sh0, sh1, sh2) -> [CInt] Source #

data Symmetric symmetry shiftTime shiftSpectrum n Source #

Shape for stored data of symmetric vectors. Even is for Cosine transform, Odd for Sine transform. shiftTime refers to no or halfway shift of the data, shiftSpectrum refers to no or halfway shift of the Cosine or Sine spectrum.

0 means Exact, 1 means Halfway:

  • Even 0 0: even around 0 and even around n-1.
  • Even 1 0: even around -0.5 and even around n-0.5.
  • Even 0 1: even around 0 and odd around n.
  • Even 1 1: even around -0.5 and odd around n-0.5.
  • Odd 0 0: odd around -1 and odd around n.
  • Odd 1 0: odd around -0.5 and odd around n-0.5.
  • Odd 0 1: odd around -1 and even around n-1.
  • Odd 1 1: odd around -0.5 and even around n-0.5.

We could pad data of Even symmetric vectors, but we cannot pad data of Odd symmetric vectors, because ! would have to involve negate. Thus we provide no padding, at all.

Constructors

Symmetric (SymmetrySingleton symmetry) (ShiftSingleton shiftTime) (ShiftSingleton shiftSpectrum) n 
Instances
Eq n => Eq (Symmetric symmetry shiftTime shiftSpectrum n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

(==) :: Symmetric symmetry shiftTime shiftSpectrum n -> Symmetric symmetry shiftTime shiftSpectrum n -> Bool #

(/=) :: Symmetric symmetry shiftTime shiftSpectrum n -> Symmetric symmetry shiftTime shiftSpectrum n -> Bool #

Show n => Show (Symmetric symmetry shiftTime shiftSpectrum n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

showsPrec :: Int -> Symmetric symmetry shiftTime shiftSpectrum n -> ShowS #

show :: Symmetric symmetry shiftTime shiftSpectrum n -> String #

showList :: [Symmetric symmetry shiftTime shiftSpectrum n] -> ShowS #

(Symmetry symmetry, Shift shiftTime, Shift shiftSpectrum, Integral n) => C (Symmetric symmetry shiftTime shiftSpectrum n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

size :: Symmetric symmetry shiftTime shiftSpectrum n -> Int #

(Symmetry symmetry, Shift shiftTime, Shift shiftSpectrum, Integral n) => Indexed (Symmetric symmetry shiftTime shiftSpectrum n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Associated Types

type Index (Symmetric symmetry shiftTime shiftSpectrum n) :: Type #

Methods

indices :: Symmetric symmetry shiftTime shiftSpectrum n -> [Index (Symmetric symmetry shiftTime shiftSpectrum n)] #

offset :: Symmetric symmetry shiftTime shiftSpectrum n -> Index (Symmetric symmetry shiftTime shiftSpectrum n) -> Int #

uncheckedOffset :: Symmetric symmetry shiftTime shiftSpectrum n -> Index (Symmetric symmetry shiftTime shiftSpectrum n) -> Int #

unifiedOffset :: Checking check => Symmetric symmetry shiftTime shiftSpectrum n -> Index (Symmetric symmetry shiftTime shiftSpectrum n) -> Result check Int #

inBounds :: Symmetric symmetry shiftTime shiftSpectrum n -> Index (Symmetric symmetry shiftTime shiftSpectrum n) -> Bool #

sizeOffset :: Symmetric symmetry shiftTime shiftSpectrum n -> (Int, Index (Symmetric symmetry shiftTime shiftSpectrum n) -> Int) #

uncheckedSizeOffset :: Symmetric symmetry shiftTime shiftSpectrum n -> (Int, Index (Symmetric symmetry shiftTime shiftSpectrum n) -> Int) #

unifiedSizeOffset :: Checking check => Symmetric symmetry shiftTime shiftSpectrum n -> (Int, Index (Symmetric symmetry shiftTime shiftSpectrum n) -> Result check Int) #

(Symmetry symmetry, Shift shiftTime, Shift shiftSpectrum, Integral n) => InvIndexed (Symmetric symmetry shiftTime shiftSpectrum n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

indexFromOffset :: Symmetric symmetry shiftTime shiftSpectrum n -> Int -> Index (Symmetric symmetry shiftTime shiftSpectrum n) #

uncheckedIndexFromOffset :: Symmetric symmetry shiftTime shiftSpectrum n -> Int -> Index (Symmetric symmetry shiftTime shiftSpectrum n) #

unifiedIndexFromOffset :: Checking check => Symmetric symmetry shiftTime shiftSpectrum n -> Int -> Result check (Index (Symmetric symmetry shiftTime shiftSpectrum n)) #

(Symmetry symmetry, Shift shiftTime, Shift shiftSpectrum, NFData n) => NFData (Symmetric symmetry shiftTime shiftSpectrum n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

rnf :: Symmetric symmetry shiftTime shiftSpectrum n -> () #

type Index (Symmetric symmetry shiftTime shiftSpectrum n) Source # 
Instance details

Defined in Numeric.FFTW.Shape

type Index (Symmetric symmetry shiftTime shiftSpectrum n) = n

symmetric :: (Symmetry symmetry, Shift shiftTime, Shift shiftSpectrum) => n -> Symmetric symmetry shiftTime shiftSpectrum n Source #

symmetricLogicalSize :: Num n => Symmetric symmetry shiftTime shiftSpectrum n -> n Source #

class Symmetry symm where Source #

Methods

switchSymmetry :: f Even -> f Odd -> f symm Source #

Instances
Symmetry Odd Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

switchSymmetry :: f Even -> f Odd -> f Odd Source #

Symmetry Even Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

switchSymmetry :: f Even -> f Odd -> f Even Source #

data SymmetrySingleton symm where Source #

Instances
Eq (SymmetrySingleton symm) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Show (SymmetrySingleton symm) Source # 
Instance details

Defined in Numeric.FFTW.Shape

NFData (SymmetrySingleton symm) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

rnf :: SymmetrySingleton symm -> () #

data Even Source #

Instances
Symmetry Even Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

switchSymmetry :: f Even -> f Odd -> f Even Source #

data Odd Source #

Instances
Symmetry Odd Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

switchSymmetry :: f Even -> f Odd -> f Odd Source #

class Shift shift where Source #

Methods

switchShift :: f Exact -> f Halfway -> f shift Source #

Instances
Shift Halfway Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

switchShift :: f Exact -> f Halfway -> f Halfway Source #

Shift Exact Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

switchShift :: f Exact -> f Halfway -> f Exact Source #

data ShiftSingleton shift where Source #

Instances
Eq (ShiftSingleton shift) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

(==) :: ShiftSingleton shift -> ShiftSingleton shift -> Bool #

(/=) :: ShiftSingleton shift -> ShiftSingleton shift -> Bool #

Show (ShiftSingleton shift) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

showsPrec :: Int -> ShiftSingleton shift -> ShowS #

show :: ShiftSingleton shift -> String #

showList :: [ShiftSingleton shift] -> ShowS #

NFData (ShiftSingleton shift) Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

rnf :: ShiftSingleton shift -> () #

data Exact Source #

Instances
Shift Exact Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

switchShift :: f Exact -> f Halfway -> f Exact Source #

data Halfway Source #

Instances
Shift Halfway Source # 
Instance details

Defined in Numeric.FFTW.Shape

Methods

switchShift :: f Exact -> f Halfway -> f Halfway Source #