feldspar-language-0.3.2: A functional embedded language for DSP and parallelism

Feldspar.Core.Functions

Contents

Description

Primitive and helper functions supported by Feldspar

Synopsis

Misc.

noSizeProp2 :: a -> b -> ()Source

class (Eq a, Storable a) => Eq a whereSource

Methods

(==) :: Data a -> Data a -> Data BoolSource

(/=) :: Data a -> Data a -> Data BoolSource

optEq :: (Storable a, Size a ~ Range b, Ord b, Num b) => Data a -> Data a -> Data BoolSource

optNeq :: (Storable a, Size a ~ Range b, Ord b, Num b) => Data a -> Data a -> Data BoolSource

class (Ord a, Eq a, Storable a) => Ord a whereSource

Methods

(<) :: Data a -> Data a -> Data BoolSource

(>) :: Data a -> Data a -> Data BoolSource

(<=) :: Data a -> Data a -> Data BoolSource

(>=) :: Data a -> Data a -> Data BoolSource

min :: Data a -> Data a -> Data aSource

max :: Data a -> Data a -> Data aSource

optLT :: (Storable a, Ord a, Size a ~ Range b, Ord b, Num b) => Data a -> Data a -> Data BoolSource

optGT :: (Storable a, Ord a, Size a ~ Range b, Ord b, Num b) => Data a -> Data a -> Data BoolSource

optLTE :: (Storable a, Ord a, Size a ~ Range b, Ord b, Num b) => Data a -> Data a -> Data BoolSource

optGTE :: (Storable a, Ord a, Size a ~ Range b, Ord b, Num b) => Data a -> Data a -> Data BoolSource

optMin :: (Ord a, Size a ~ Range b, Ord b, Num b) => Data a -> Data a -> Data aSource

optMax :: (Ord a, Size a ~ Range b, Ord b, Num b) => Data a -> Data a -> Data aSource

(?) :: Computable a => Data Bool -> (a, a) -> aSource

Selects the elements of the pair depending on the condition

(&&*) :: Computable a => (a -> Data Bool) -> (a -> Data Bool) -> a -> Data BoolSource

Lazy conjunction, second argument only run if necessary

(||*) :: Computable a => (a -> Data Bool) -> (a -> Data Bool) -> a -> Data BoolSource

Lazy disjunction, second argument only run if necessary

optRem :: (Integral a, Size a ~ Range b, Ord b, Num b, Enum b) => Data a -> Data a -> Data aSource

optMod :: (Integral a, Size a ~ Range b, Ord b, Num b, Enum b) => Data a -> Data a -> Data aSource

optSignedExp :: (Integral a, Bits a, Storable a, Size a ~ Range b, Ord b, Num b) => Data a -> Data a -> Data aSource

optExp :: (Integral a, Storable a) => Data a -> Data a -> Data aSource

Loops

for :: Computable a => Data Int -> Data Int -> a -> (Data Int -> a -> a) -> aSource

For-loop

for start end init body:

  • start/end are the start/end indexes.
  • init is the starting state.
  • body computes the next state given the current loop index (ranging over [start .. end]) and the current state.

unfoldCore :: (Computable state, Storable a) => Data Length -> state -> (Data Int -> state -> (Data a, state)) -> (Data [a], state)Source

A sequential "unfolding" of an vector

unfoldCore l init step:

  • l is the length of the resulting vector.
  • init is the initial state.
  • step is a function computing a new element and the next state from the current index and current state. The index is the position of the new element in the output vector.

absNum' :: (Numeric a, Num (Size a)) => Data a -> Data aSource

optAbs :: (Numeric a, Size a ~ Range b, Num b, Ord b) => Data a -> Data aSource

signumNum' :: (Numeric a, Num (Size a)) => Data a -> Data aSource

optSignum :: (Numeric a, Size a ~ Range b, Num b, Ord b) => Data a -> Data aSource

optAdd :: (Numeric a, Num (Size a)) => Data a -> Data a -> Data aSource

optSub :: (Numeric a, Num (Size a)) => Data a -> Data a -> Data aSource

optMul :: (Numeric a, Num (Size a)) => Data a -> Data a -> Data aSource

Bit manipulation

class (Bits a, Storable a) => Bits a whereSource

The following class provides functions for bit level manipulation

Methods

(.&.) :: Data a -> Data a -> Data aSource

(.|.) :: Data a -> Data a -> Data aSource

xor :: Data a -> Data a -> Data aSource

(⊕) :: Data a -> Data a -> Data aSource

complement :: Data a -> Data aSource

bit :: Data Int -> Data aSource

setBit :: Data a -> Data Int -> Data aSource

clearBit :: Data a -> Data Int -> Data aSource

complementBit :: Data a -> Data Int -> Data aSource

testBit :: Data a -> Data Int -> Data BoolSource

shiftL :: Data a -> Data Int -> Data aSource

(<<) :: Data a -> Data Int -> Data aSource

shiftR :: Data a -> Data Int -> Data aSource

(>>) :: Data a -> Data Int -> Data aSource

rotateL :: Data a -> Data Int -> Data aSource

rotateR :: Data a -> Data Int -> Data aSource

reverseBits :: Data a -> Data aSource

bitScan :: Data a -> Data IntSource

Returns the number of leading zeroes for unsigned types. For signed types it returns the number of unnecessary sign bits

bitCount :: Data a -> Data IntSource

bitSize :: Data a -> Data IntSource

isSigned :: Data a -> Data BoolSource

optAnd :: (Bits a, Storable a) => Data a -> Data a -> Data aSource

optOr :: (Bits a, Storable a) => Data a -> Data a -> Data aSource

optXor :: (Bits a, Bits a, Storable a) => Data a -> Data a -> Data aSource

allOnes :: (Eq a, Bits a) => a -> BoolSource

optZero :: (a -> Data Int -> a) -> a -> Data Int -> aSource

scanLeft :: Bits b => b -> IntSource

countBits :: Bits b => b -> IntSource

revBits :: Bits b => b -> bSource