sdr-0.1.0.8: A software defined radio library

Safe HaskellNone
LanguageHaskell2010

SDR.Util

Contents

Description

Various utiliy signal processing functions

Synopsis

Classes

class Mult a b where Source #

A class for things that can be multiplied by a scalar.

Minimal complete definition

mult

Methods

mult :: a -> b -> a Source #

Instances

Num a => Mult a a Source # 

Methods

mult :: a -> a -> a Source #

Num a => Mult (Complex a) a Source # 

Methods

mult :: Complex a -> a -> Complex a Source #

mult :: Mult a b => a -> b -> a Source #

Conversion to floating point for reception

RTLSDR

interleavedIQUnsigned256ToFloat :: (Num a, Integral a, Num b, Fractional b, Vector v1 a, Vector v2 (Complex b)) => v1 a -> v2 (Complex b) Source #

Create a vector of complex floating samples from a vector of interleaved I Q components. Each input element ranges from 0 to 255. This is the format that RTLSDR devices use.

interleavedIQUnsignedByteToFloat :: Vector CUChar -> Vector (Complex Float) Source #

Same as interleavedIQUnsigned256ToFloat but written in C and specialized for unsigned byte inputs and Float outputs.

interleavedIQUnsignedByteToFloatSSE :: Vector CUChar -> Vector (Complex Float) Source #

Same as interleavedIQUnsigned256ToFloat but written in C using SSE intrinsics and specialized for unsigned byte inputs and Float outputs.

interleavedIQUnsignedByteToFloatAVX :: Vector CUChar -> Vector (Complex Float) Source #

Same as interleavedIQUnsigned256ToFloat but written in C using AVX intrinsics and specialized for unsigned byte inputs and Float outputs.

interleavedIQUnsignedByteToFloatFast :: CPUInfo -> Vector CUChar -> Vector (Complex Float) Source #

Same as interleavedIQUnsigned256ToFloat but uses the fastest SIMD instruction set your processor supports and specialized for unsigned byte inputs and Float outputs.

BladeRF

interleavedIQSigned2048ToFloat :: (Num a, Integral a, Num b, Fractional b, Vector v1 a, Vector v2 (Complex b)) => v1 a -> v2 (Complex b) Source #

Create a vector of complex float samples from a vector of interleaved I Q components. Each input element ranges from -2048 to 2047. This is the format that the BladeRF uses.

interleavedIQSignedWordToFloat :: Vector CShort -> Vector (Complex Float) Source #

Same as interleavedIQUnsigned256ToFloat but written in C and specialized for signed short inputs and Float outputs.

interleavedIQSignedWordToFloatSSE :: Vector CShort -> Vector (Complex Float) Source #

Same as interleavedIQUnsigned256ToFloat but written in C using SSE intrinsics and specialized for signed short inputs and Float outputs.

interleavedIQSignedWordToFloatAVX :: Vector CShort -> Vector (Complex Float) Source #

Same as interleavedIQUnsigned256ToFloat but written in C using AVX intrinsics and specialized for signed short inputs and Float outputs.

interleavedIQSignedWordToFloatFast :: CPUInfo -> Vector CShort -> Vector (Complex Float) Source #

Same as interleavedIQSigned2048ToFloat but uses the fastest SIMD instruction set your processor supports and specialized for signed short inputs and Float outputs.

Conversion from floating point for transmission

BladeRF

complexFloatToInterleavedIQSigned2048 :: (Integral b, RealFrac a, Vector v1 (Complex a), Vector v2 b) => v1 (Complex a) -> v2 b Source #

Create a vector of interleaved I Q component integral samples from a vector of complex Floats. Each input ranges from -2048 to 2047. This is the format the BladeRF uses.

complexFloatToInterleavedIQSignedWord :: Vector (Complex Float) -> Vector CShort Source #

Same as complexFloatToInterleavedIQSigned2048 but written in C and specialized for Float inputs and signed short outputs.

Scaling

scaleC Source #

Arguments

:: Float

Scale factor

-> Vector Float

Input vector

-> MVector RealWorld Float

Output vector

-> IO () 

Scale a vector, written in C

scaleCSSE Source #

Arguments

:: Float

Scale factor

-> Vector Float

Input vector

-> MVector RealWorld Float

Output vector

-> IO () 

Scale a vector, written in C using SSE intrinsics

scaleCAVX Source #

Arguments

:: Float

Scale factor

-> Vector Float

Input vector

-> MVector RealWorld Float

Output vector

-> IO () 

Scale a vector, written in C using AVX intrinsics

scaleFast :: CPUInfo -> Float -> Vector Float -> MVector RealWorld Float -> IO () Source #

Scale a vector. Uses the fastest SIMD instruction set your processor supports.

Mapping over complex numbers

cplxMap Source #

Arguments

:: (a -> b)

The function

-> Complex a

Input complex number

-> Complex b

Output complex number

Apply a function to both parts of a complex number

Frequency shifting

halfBandUp Source #

Arguments

:: (Vector v n, Num n) 
=> Int

The length of the Vector

-> v n 

Multiplication by this vector shifts all frequencies up by 1/2 of the sampling frequency

quarterBandUp Source #

Arguments

:: (Vector v (Complex n), Num n) 
=> Int

The length of the Vector

-> v (Complex n) 

Multiplication by this vector shifts all frequencies up by 1/4 of the sampling frequency

Data streams

streamString Source #

Arguments

:: (FiniteBits b, Monad m) 
=> [b]

The string whose bits are to be streamed

-> Int

The size of each streamed vector

-> Producer (Vector Float) m () 

A Producer that streams vectors of the bits that make up the string argument concatenated repeatedly. Each bit is encoded as a float with value (+1) for 1 and (-1) for 0.

streamRandom Source #

Arguments

:: PrimMonad m 
=> Int

The size of each streamed vector

-> Producer (Vector Float) m () 

A Producer that streams vectors of random bits. Each bit is encoded as a float with value (+1) for 1 and (-1) for 0.

Automatic gain control

agc Source #

Arguments

:: (Num a, Storable a, RealFloat a) 
=> a

a

-> a

reference

-> a

initial state

-> Vector (Complex a)

input vector

-> (a, Vector (Complex a))

(final state, output vector)

Simple automatic gain control

agcPipe Source #

Arguments

:: (Num a, Storable a, RealFloat a, Monad m) 
=> a

a

-> a

reference

-> Pipe (Vector (Complex a)) (Vector (Complex a)) m () 

Simple automatic gain control pipe

Squashing initialization into the Pipe

combineInit :: (Monad m, MonadTrans t, Monad (t m)) => m (t m a) -> t m a Source #

Specializes to combineInit :: IO (Pipe a b IO ()) -> Pipe a b IO ()

combineInitTrans :: (Monad (t1 m), Monad (t (t1 m)), MonadTrans t, Monad m, MFunctor t, MonadTrans t1) => t1 m (t m a) -> t (t1 m) a Source #

Specializes to combineInitTrans :: EitherT String IO (Pipe a b IO ()) -> Pipe a b (EitherT String IO) ()