sdr-0.1.0.2: A software defined radio library

Safe HaskellNone
LanguageHaskell2010

SDR.Filter

Contents

Description

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

Types

data Filter m v vm a Source

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.

Constructors

Filter 

Fields

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 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.

Constructors

Decimator 

Fields

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 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.

Constructors

forall dat . Resampler 

Fields

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)
 

Helper Functions

Filters

haskellFilter Source

Arguments

:: (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 Filter data structure

Returns a slow Filter data structure entirely implemented in Haskell

Real Data

fastFilterCR Source

Arguments

:: [Float]

The filter coefficients

-> IO (Filter IO Vector MVector Float)

The Filter data structure

Returns a fast Filter data structure implemented in C. For filtering real data with real coefficients.

fastFilterSSER Source

Arguments

:: [Float]

The filter coefficients

-> IO (Filter IO Vector MVector Float)

The Filter data structure

Returns a fast Filter data structure implemented in C using SSE instructions. For filtering real data with real coefficients.

fastFilterAVXR Source

Arguments

:: [Float]

The filter coefficients

-> IO (Filter IO Vector MVector Float)

The Filter data structure

Returns a fast Filter data structure implemented in C using AVX instructions. For filtering real data with real coefficients.

fastFilterR Source

Arguments

:: CPUInfo

The CPU's capabilities

-> [Float]

The filter coefficients

-> IO (Filter IO Vector MVector Float)

The Filter data structure

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

fastFilterCC Source

Arguments

:: [Float]

The filter coefficients

-> IO (Filter IO Vector MVector (Complex Float))

The Filter data structure

Returns a fast Filter data structure implemented in C For filtering complex data with real coefficients.

fastFilterSSEC Source

Arguments

:: [Float]

The filter coefficients

-> IO (Filter IO Vector MVector (Complex Float))

The Filter data structure

Returns a fast Filter data structure implemented in C using SSE instructions. For filtering complex data with real coefficients.

fastFilterAVXC Source

Arguments

:: [Float]

The filter coefficients

-> IO (Filter IO Vector MVector (Complex Float))

The Filter data structure

Returns a fast Filter data structure implemented in C using AVX instructions. For filtering complex data with real coefficients.

fastFilterC Source

Arguments

:: CPUInfo

The CPU's capabilities

-> [Float]

The filter coefficients

-> IO (Filter IO Vector MVector (Complex Float))

The Filter data structure

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

fastFilterSymSSER Source

Arguments

:: [Float]

The first half of the filter coefficients

-> IO (Filter IO Vector MVector Float)

The Filter data structure

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.

fastFilterSymAVXR Source

Arguments

:: [Float]

The first half of the filter coefficients

-> IO (Filter IO Vector MVector Float)

The Filter data structure

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.

fastFilterSymR Source

Arguments

:: CPUInfo

The CPU's capabilities

-> [Float]

The filter coefficients

-> IO (Filter IO Vector MVector Float)

The Filter data structure

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

haskellDecimator Source

Arguments

:: (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 Decimator data structure

Returns a slow Decimator data structure entirely implemented in Haskell

Real Data

fastDecimatorCR Source

Arguments

:: Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Decimator IO Vector MVector Float)

The Decimator data structure

Returns a fast Decimator data structure implemented in C. For decimating real data with real coefficients.

fastDecimatorSSER Source

Arguments

:: Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Decimator IO Vector MVector Float)

The Decimator data structure

Returns a fast Decimator data structure implemented in C using SSE instructions. For decimating real data with real coefficients.

fastDecimatorAVXR Source

Arguments

:: Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Decimator IO Vector MVector Float)

The Decimator data structure

Returns a fast Decimator data structure implemented in C using AVX instructions. For decimating real data with real coefficients.

fastDecimatorR Source

Arguments

:: CPUInfo

The CPU's capabilities

-> Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Decimator IO Vector MVector Float)

The Decimator data structure

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

fastDecimatorCC Source

Arguments

:: Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Decimator IO Vector MVector (Complex Float))

The Decimator data structure

Returns a fast Decimator data structure implemented in C. For decimating complex data with real coefficients.

fastDecimatorSSEC Source

Arguments

:: Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Decimator IO Vector MVector (Complex Float))

The Decimator data structure

Returns a fast Decimator data structure implemented in C using SSE instructions. For decimating complex data with real coefficients.

fastDecimatorAVXC Source

Arguments

:: Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Decimator IO Vector MVector (Complex Float))

The Decimator data structure

Returns a fast Decimator data structure implemented in C using AVX instructions. For decimating complex data with real coefficients.

fastDecimatorC Source

Arguments

:: CPUInfo

The CPU's capabilities

-> Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Decimator IO Vector MVector (Complex Float))

The Decimator data structure

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

fastDecimatorSymSSER Source

Arguments

:: Int

The decimation factor

-> [Float]

The first half of the filter coefficients

-> IO (Decimator IO Vector MVector Float)

The Decimator data structure

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.

fastDecimatorSymAVXR Source

Arguments

:: Int

The decimation factor

-> [Float]

The first half of the filter coefficients

-> IO (Decimator IO Vector MVector Float)

The Decimator data structure

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.

fastDecimatorSymR Source

Arguments

:: CPUInfo

The CPU's capabilities

-> Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Decimator IO Vector MVector Float)

The Decimator data structure

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

haskellResampler Source

Arguments

:: (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 Resampler data structure

Returns a slow Resampler data structure entirely implemented in Haskell

Real Data

fastResamplerCR Source

Arguments

:: Int

The interpolation factor

-> Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Resampler IO Vector MVector Float)

The Resampler data structure

Returns a fast Resampler data structure implemented in C. For filtering real data with real coefficients.

fastResamplerSSER Source

Arguments

:: Int

The interpolation factor

-> Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Resampler IO Vector MVector Float)

The Resampler data structure

Returns a fast Resampler data structure implemented in C using SSE instructions. For filtering real data with real coefficients.

fastResamplerAVXR Source

Arguments

:: Int

The interpolation factor

-> Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Resampler IO Vector MVector Float)

The Resampler data structure

Returns a fast Resampler data structure implemented in C using AVX instructions. For filtering real data with real coefficients.

fastResamplerR Source

Arguments

:: CPUInfo

The CPU's capabilities

-> Int

The interpolation factor

-> Int

The decimation factor

-> [Float]

The filter coefficients

-> IO (Resampler IO Vector MVector Float)

The Resampler data structure

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.

Filter

firFilter Source

Arguments

:: (PrimMonad m, Functor m, Vector v a, Num a) 
=> Filter m v (Mutable v) a

The Filter data structure

-> Int

The output block size

-> Pipe (v a) (v a) m ()

The Pipe that does the filtering

Create a pipe that performs filtering

Decimate

firDecimator Source

Arguments

:: (PrimMonad m, Functor m, Vector v a, Num a) 
=> Decimator m v (Mutable v) a

The Decimator data structure

-> Int

The output block size

-> Pipe (v a) (v a) m ()

The Pipe that does the decimation

Create a pipe that performs decimation

Resample

firResampler Source

Arguments

:: (PrimMonad m, Vector v a, Num a) 
=> Resampler m v (Mutable v) a

The Resampler data structure

-> Int

The output block size

-> Pipe (v a) (v a) m ()

The Pipe that does the resampling

Create a pipe that performs resampling

DC Blocking Filter

dcBlockingFilter :: Pipe (Vector Float) (Vector Float) IO () Source

A DC blocking filter