Safe Haskell | None |
---|---|
Language | Haskell2010 |
FIR filtering, decimation and resampling.
FIR filters (and decimators, resamplers) work by taking successive dot products between the filter coefficients and the input data at increasing offsets. Sometimes the dot product fits entirely within one input buffer and other times it spans two input buffers (but never more because we assume that the filter length is less than the buffer size).
We divide the filtering code by these two cases. Each filter (or decimator, resampler) is described by a data structure such as Filter
with two functions, one for filtering within a single buffer and one that crosses buffers.
The user must first create one of these data structures using the helper functions and pass this data structure to one of firFilter
, firDecimator
, or firResampler
to create the Pipe
that does the filtering. For example:
decimatorStruct <- fastDecimatorC cpuInfo decimation coeffs let decimatorPipe :: Pipe (Vector (Complex Float)) (Vector (Complex Float)) IO () decimatorPipe = firDecimator decimatorStruct outputSize
There are polymorphic Haskell only implementations of filtering, decimation and resampling, for example, haskellFilter
. In addition, there are optimised C implementations that use SIMD instructions on x86 machines, such as fastFilterR
. These are always specialized to either real or complex numbers. There are also even faster implementations specialized for the case where the filter coefficients are symmetric as in a linear phase filter such as fastFilterSymR
.
The Haskell implementations are reasonably fast due to the Vector library and GHC's LLVM backend, however, if speed is important you are much better off with the C implementations.
In the future we may avoid the cross buffer filtering function by mapping the buffers consecutively in memory as (I believe) GNU Radio does.
An extensive benchmark suite exists in the /benchmarks subdirectory of this package.
Synopsis
- data Filter m v vm a = Filter {
- numCoeffsF :: Int
- filterOne :: Int -> v a -> vm (PrimState m) a -> m ()
- filterCross :: Int -> v a -> v a -> vm (PrimState m) a -> m ()
- data Decimator m v vm a = Decimator {
- numCoeffsD :: Int
- decimationD :: Int
- decimateOne :: Int -> v a -> vm (PrimState m) a -> m ()
- decimateCross :: Int -> v a -> v a -> vm (PrimState m) a -> m ()
- data Resampler m v vm a = Resampler {
- numCoeffsR :: Int
- decimationR :: Int
- interpolationR :: Int
- startDat :: dat
- resampleOne :: dat -> Int -> v a -> vm (PrimState m) a -> m (dat, Int)
- resampleCross :: dat -> Int -> v a -> v a -> vm (PrimState m) a -> m (dat, Int)
- haskellFilter :: (PrimMonad m, Functor m, Num a, Mult a b, Vector v a, Vector v b, MVector vm a) => [b] -> IO (Filter m v vm a)
- fastFilterCR :: [Float] -> IO (Filter IO Vector MVector Float)
- fastFilterSSER :: [Float] -> IO (Filter IO Vector MVector Float)
- fastFilterAVXR :: [Float] -> IO (Filter IO Vector MVector Float)
- fastFilterR :: CPUInfo -> [Float] -> IO (Filter IO Vector MVector Float)
- fastFilterCC :: [Float] -> IO (Filter IO Vector MVector (Complex Float))
- fastFilterSSEC :: [Float] -> IO (Filter IO Vector MVector (Complex Float))
- fastFilterAVXC :: [Float] -> IO (Filter IO Vector MVector (Complex Float))
- fastFilterC :: CPUInfo -> [Float] -> IO (Filter IO Vector MVector (Complex Float))
- fastFilterSymSSER :: [Float] -> IO (Filter IO Vector MVector Float)
- fastFilterSymAVXR :: [Float] -> IO (Filter IO Vector MVector Float)
- fastFilterSymR :: CPUInfo -> [Float] -> IO (Filter IO Vector MVector Float)
- haskellDecimator :: (PrimMonad m, Functor m, Num a, Mult a b, Vector v a, Vector v b, MVector vm a) => Int -> [b] -> IO (Decimator m v vm a)
- fastDecimatorCR :: Int -> [Float] -> IO (Decimator IO Vector MVector Float)
- fastDecimatorSSER :: Int -> [Float] -> IO (Decimator IO Vector MVector Float)
- fastDecimatorAVXR :: Int -> [Float] -> IO (Decimator IO Vector MVector Float)
- fastDecimatorR :: CPUInfo -> Int -> [Float] -> IO (Decimator IO Vector MVector Float)
- fastDecimatorCC :: Int -> [Float] -> IO (Decimator IO Vector MVector (Complex Float))
- fastDecimatorSSEC :: Int -> [Float] -> IO (Decimator IO Vector MVector (Complex Float))
- fastDecimatorAVXC :: Int -> [Float] -> IO (Decimator IO Vector MVector (Complex Float))
- fastDecimatorC :: CPUInfo -> Int -> [Float] -> IO (Decimator IO Vector MVector (Complex Float))
- fastDecimatorSymSSER :: Int -> [Float] -> IO (Decimator IO Vector MVector Float)
- fastDecimatorSymAVXR :: Int -> [Float] -> IO (Decimator IO Vector MVector Float)
- fastDecimatorSymR :: CPUInfo -> Int -> [Float] -> IO (Decimator IO Vector MVector Float)
- haskellResampler :: (PrimMonad m, Functor m, Num a, Mult a b, Vector v a, Vector v b, MVector vm a) => Int -> Int -> [b] -> IO (Resampler m v vm a)
- fastResamplerCR :: Int -> Int -> [Float] -> IO (Resampler IO Vector MVector Float)
- fastResamplerSSER :: Int -> Int -> [Float] -> IO (Resampler IO Vector MVector Float)
- fastResamplerAVXR :: Int -> Int -> [Float] -> IO (Resampler IO Vector MVector Float)
- fastResamplerR :: CPUInfo -> Int -> Int -> [Float] -> IO (Resampler IO Vector MVector Float)
- fastResamplerCC :: Int -> Int -> [Float] -> IO (Resampler IO Vector MVector (Complex Float))
- fastResamplerSSEC :: Int -> Int -> [Float] -> IO (Resampler IO Vector MVector (Complex Float))
- fastResamplerAVXC :: Int -> Int -> [Float] -> IO (Resampler IO Vector MVector (Complex Float))
- fastResamplerC :: CPUInfo -> Int -> Int -> [Float] -> IO (Resampler IO Vector MVector (Complex Float))
- firFilter :: (PrimMonad m, Functor m, Vector v a, Num a) => Filter m v (Mutable v) a -> Int -> Pipe (v a) (v a) m ()
- firDecimator :: (PrimMonad m, Functor m, Vector v a, Num a) => Decimator m v (Mutable v) a -> Int -> Pipe (v a) (v a) m ()
- firResampler :: (PrimMonad m, Vector v a, Num a) => Resampler m v (Mutable v) a -> Int -> Pipe (v a) (v a) m ()
- dcBlockingFilter :: Pipe (Vector Float) (Vector Float) IO ()
Types
A Filter
contains all of the information needed by the filterr
function to perform filtering. i.e. it contains the filter coefficients
and pointers to the functions to do the actual filtering.
Filter | |
|
data Decimator m v vm a Source #
A Decimator
contains all of the information needed by the decimate
function to perform decimation i.e. it contains the filter coefficients
and pointers to the functions to do the actual decimation.
Decimator | |
|
data Resampler m v vm a Source #
A Resampler
contains all of the information needed by the resample
function to perform resampling i.e. it contains the filter coefficients
and pointers to the functions to do the actual resampling.
Resampler | |
|
Helper Functions
Filters
:: (PrimMonad m, Functor m, Num a, Mult a b, Vector v a, Vector v b, MVector vm a) | |
=> [b] | The filter coefficients |
-> IO (Filter m v vm a) | The |
Returns a slow Filter data structure entirely implemented in Haskell
Real Data
Returns a fast Filter data structure implemented in C. For filtering real data with real coefficients.
Returns a fast Filter data structure implemented in C using SSE instructions. For filtering real data with real coefficients.
Returns a fast Filter data structure implemented in C using AVX instructions. For filtering real data with real coefficients.
:: CPUInfo | The CPU's capabilities |
-> [Float] | The filter coefficients |
-> IO (Filter IO Vector MVector Float) | The |
Returns a fast Filter data structure implemented in C using the fastest SIMD instruction set your processor supports. For filtering real data with real coefficients.
Complex Data
:: [Float] | The filter coefficients |
-> IO (Filter IO Vector MVector (Complex Float)) | The |
Returns a fast Filter data structure implemented in C For filtering complex data with real coefficients.
:: [Float] | The filter coefficients |
-> IO (Filter IO Vector MVector (Complex Float)) | The |
Returns a fast Filter data structure implemented in C using SSE instructions. For filtering complex data with real coefficients.
:: [Float] | The filter coefficients |
-> IO (Filter IO Vector MVector (Complex Float)) | The |
Returns a fast Filter data structure implemented in C using AVX instructions. For filtering complex data with real coefficients.
:: CPUInfo | The CPU's capabilities |
-> [Float] | The filter coefficients |
-> IO (Filter IO Vector MVector (Complex Float)) | The |
Returns a fast Filter data structure implemented in C using the fastest SIMD instruction set your processor supports. For filtering complex data with real coefficients.
Linear Phase Real Data
:: [Float] | The first half of the filter coefficients |
-> IO (Filter IO Vector MVector Float) | The |
Returns a fast Filter data structure implemented in C using SSE instructions. For filtering real data with real coefficients. For filters with symmetric coefficients, i.e. 'linear phase'. Coefficient length must be a multiple of 4.
:: [Float] | The first half of the filter coefficients |
-> IO (Filter IO Vector MVector Float) | The |
Returns a fast Filter data structure implemented in C using AVX instructions. For filtering real data with real coefficients. For filters with symmetric coefficients, i.e. 'linear phase'. Coefficient length must be a multiple of 4.
:: CPUInfo | The CPU's capabilities |
-> [Float] | The filter coefficients |
-> IO (Filter IO Vector MVector Float) | The |
Returns a fast Filter data structure implemented in C using the fastest SIMD instruction set your processor supports. For filtering complex data with real coefficients. For filters with symmetric coefficients, i.e. 'linear phase'. Coefficient length must be a multiple of 4.
Decimators
:: (PrimMonad m, Functor m, Num a, Mult a b, Vector v a, Vector v b, MVector vm a) | |
=> Int | The decimation factor |
-> [b] | The filter coefficients |
-> IO (Decimator m v vm a) | The |
Returns a slow Decimator data structure entirely implemented in Haskell
Real Data
:: Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Decimator IO Vector MVector Float) | The |
Returns a fast Decimator data structure implemented in C. For decimating real data with real coefficients.
:: Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Decimator IO Vector MVector Float) | The |
Returns a fast Decimator data structure implemented in C using SSE instructions. For decimating real data with real coefficients.
:: Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Decimator IO Vector MVector Float) | The |
Returns a fast Decimator data structure implemented in C using AVX instructions. For decimating real data with real coefficients.
:: CPUInfo | The CPU's capabilities |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Decimator IO Vector MVector Float) | The |
Returns a fast Decimator data structure implemented in C using the fastest SIMD instruction set your processor supports. For decimating real data with real coefficients.
Complex Data
:: Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Decimator IO Vector MVector (Complex Float)) | The |
Returns a fast Decimator data structure implemented in C. For decimating complex data with real coefficients.
:: Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Decimator IO Vector MVector (Complex Float)) | The |
Returns a fast Decimator data structure implemented in C using SSE instructions. For decimating complex data with real coefficients.
:: Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Decimator IO Vector MVector (Complex Float)) | The |
Returns a fast Decimator data structure implemented in C using AVX instructions. For decimating complex data with real coefficients.
:: CPUInfo | The CPU's capabilities |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Decimator IO Vector MVector (Complex Float)) | The |
Returns a fast Decimator data structure implemented in C using the fastest SIMD instruction set your processor supports. For decimating complex data with real coefficients.
Linear Phase Real Data
:: Int | The decimation factor |
-> [Float] | The first half of the filter coefficients |
-> IO (Decimator IO Vector MVector Float) | The |
Returns a fast Decimator data structure implemented in C using SSE instructions. For decimating real data with real coefficients. For decimators with symmetric coefficients, i.e. 'linear phase'. Coefficient length must be a multiple of 4.
:: Int | The decimation factor |
-> [Float] | The first half of the filter coefficients |
-> IO (Decimator IO Vector MVector Float) | The |
Returns a fast Decimator data structure implemented in C using AVX instructions. For decimating real data with real coefficients. For decimators with symmetric coefficients, i.e. 'linear phase'. Coefficient length must be a multiple of 4.
:: CPUInfo | The CPU's capabilities |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Decimator IO Vector MVector Float) | The |
Returns a fast Decimator data structure implemented in C using the fastest SIMD instruction set your processor supports. For decimating real data with real coefficients. For decimators with symmetric coefficients, i.e. 'linear phase'. Coefficient length must be a multiple of 4.
Resamplers
:: (PrimMonad m, Functor m, Num a, Mult a b, Vector v a, Vector v b, MVector vm a) | |
=> Int | The interpolation factor |
-> Int | The decimation factor |
-> [b] | The filter coefficients |
-> IO (Resampler m v vm a) | The |
Returns a slow Resampler data structure entirely implemented in Haskell
Real Data
:: Int | The interpolation factor |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Resampler IO Vector MVector Float) | The |
Returns a fast Resampler data structure implemented in C. For filtering real data with real coefficients.
:: Int | The interpolation factor |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Resampler IO Vector MVector Float) | The |
Returns a fast Resampler data structure implemented in C using SSE instructions. For filtering real data with real coefficients.
:: Int | The interpolation factor |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Resampler IO Vector MVector Float) | The |
Returns a fast Resampler data structure implemented in C using AVX instructions. For filtering real data with real coefficients.
:: CPUInfo | The CPU's capabilities |
-> Int | The interpolation factor |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Resampler IO Vector MVector Float) | The |
Returns a fast Resampler data structure implemented in C using the fastest SIMD instruction set your processor supports. For resampling real data with real coefficients.
Complex Data
:: Int | The interpolation factor |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Resampler IO Vector MVector (Complex Float)) | The |
Returns a fast Resampler data structure implemented in C. For filtering complex data with real coefficients.
:: Int | The interpolation factor |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Resampler IO Vector MVector (Complex Float)) | The |
Returns a fast Resampler data structure implemented in C using SSE instructions. For filtering complex data with real coefficients.
:: Int | The interpolation factor |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Resampler IO Vector MVector (Complex Float)) | The |
Returns a fast Resampler data structure implemented in C using AVX instructions. For filtering complex data with real coefficients.
:: CPUInfo | The CPU's capabilities |
-> Int | The interpolation factor |
-> Int | The decimation factor |
-> [Float] | The filter coefficients |
-> IO (Resampler IO Vector MVector (Complex Float)) | The |
Returns a fast Resampler data structure implemented in C using the fastest SIMD instruction set your processor supports. For resampling complex data with real coefficients.
Filter
:: (PrimMonad m, Functor m, Vector v a, Num a) | |
=> Filter m v (Mutable v) a | The |
-> Int | The output block size |
-> Pipe (v a) (v a) m () | The |
Create a pipe that performs filtering
Decimate
:: (PrimMonad m, Functor m, Vector v a, Num a) | |
=> Decimator m v (Mutable v) a | The |
-> Int | The output block size |
-> Pipe (v a) (v a) m () | The |
Create a pipe that performs decimation
Resample
:: (PrimMonad m, Vector v a, Num a) | |
=> Resampler m v (Mutable v) a | The |
-> Int | The output block size |
-> Pipe (v a) (v a) m () | The |
Create a pipe that performs resampling