synthesizer-llvm-1.1.0.1: Efficient signal processing using runtime compilation

Safe HaskellNone
LanguageHaskell98

Synthesizer.LLVM.Frame.SerialVector.Plain

Description

A special vector type that represents a time-sequence of samples. This way we can distinguish safely between LLVM vectors used for parallel signals and pipelines and those used for chunky processing of scalar signals. For the chunky processing this data type allows us to derive the factor from the type that time constants have to be multiplied with.

Documentation

newtype T n a Source #

Constructors

Cons (Vector n a) 
Instances
(Eq a, Positive n) => Eq (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

(==) :: T n a -> T n a -> Bool #

(/=) :: T n a -> T n a -> Bool #

(Num a, Positive n) => Num (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

(+) :: T n a -> T n a -> T n a #

(-) :: T n a -> T n a -> T n a #

(*) :: T n a -> T n a -> T n a #

negate :: T n a -> T n a #

abs :: T n a -> T n a #

signum :: T n a -> T n a #

fromInteger :: Integer -> T n a #

(Positive n, Storable a) => Storable (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

sizeOf :: T n a -> Int #

alignment :: T n a -> Int #

peekElemOff :: Ptr (T n a) -> Int -> IO (T n a) #

pokeElemOff :: Ptr (T n a) -> Int -> T n a -> IO () #

peekByteOff :: Ptr b -> Int -> IO (T n a) #

pokeByteOff :: Ptr b -> Int -> T n a -> IO () #

peek :: Ptr (T n a) -> IO (T n a) #

poke :: Ptr (T n a) -> T n a -> IO () #

Vector n a => C (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

pack :: T n a -> Struct (T n a)

unpack :: Struct (T n a) -> T n a

(Positive n, C a) => C (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Associated Types

type Repr (T n a) :: Type

Methods

cons :: T n a -> T0 (T n a)

undef :: T0 (T n a)

zero :: T0 (T n a)

phi :: BasicBlock -> T0 (T n a) -> CodeGenFunction r (T0 (T n a))

addPhi :: BasicBlock -> T0 (T n a) -> T0 (T n a) -> CodeGenFunction r ()

(Positive n, Additive a) => Additive (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

add :: T0 (T n a) -> T0 (T n a) -> CodeGenFunction r (T0 (T n a))

sub :: T0 (T n a) -> T0 (T n a) -> CodeGenFunction r (T0 (T n a))

neg :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

(Positive n, Fraction a) => Fraction (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

truncate :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

fraction :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

(Positive n, Real a) => Real (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

min :: T0 (T n a) -> T0 (T n a) -> CodeGenFunction r (T0 (T n a))

max :: T0 (T n a) -> T0 (T n a) -> CodeGenFunction r (T0 (T n a))

abs :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

signum :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

(Positive n, IntegerConstant a) => IntegerConstant (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

fromInteger' :: Integer -> T0 (T n a)

(Positive n, PseudoRing a) => PseudoRing (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

mul :: T0 (T n a) -> T0 (T n a) -> CodeGenFunction r (T0 (T n a))

(Positive n, RationalConstant a) => RationalConstant (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

fromRational' :: Rational -> T0 (T n a)

(Positive n, Algebraic a) => Algebraic (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

sqrt :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

(Positive n, Field a) => Field (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

fdiv :: T0 (T n a) -> T0 (T n a) -> CodeGenFunction r (T0 (T n a))

(Positive n, Transcendental a) => Transcendental (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

pi :: CodeGenFunction r (T0 (T n a))

sin :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

cos :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

exp :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

log :: T0 (T n a) -> CodeGenFunction r (T0 (T n a))

pow :: T0 (T n a) -> T0 (T n a) -> CodeGenFunction r (T0 (T n a))

(Positive n, Vector a, C a) => C (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

Methods

load :: Value (Ptr (T n a)) -> CodeGenFunction r (T0 (T n a))

store :: T0 (T n a) -> Value (Ptr (T n a)) -> CodeGenFunction r ()

(Positive n, n ~ m, NativeFloating n a ar, NativeFloating a ar) => NativeFloating (T n a) (Vector m ar) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

(Positive n, n ~ m, NativeInteger n a ar, NativeInteger a ar) => NativeInteger (T n a) (Vector m ar) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

type Repr (T n a) Source # 
Instance details

Defined in Synthesizer.LLVM.Frame.SerialVector.Code

type Repr (T n a) = Repr n a

fromList :: Positive n => T [] a -> T n a Source #

replicate :: Positive n => a -> T n a Source #

iterate :: Positive n => (a -> a) -> a -> T n a Source #