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

Safe HaskellNone
LanguageHaskell98

Synthesizer.LLVM.Simple.Value

Synopsis

Documentation

data T a Source

Instances

Functor T Source 
Applicative T Source 
(Additive a, IntegerConstant a) => Enum (T a) Source 
(Transcendental a, Real a, RationalConstant a) => Floating (T a) Source 
(Field a, Real a, RationalConstant a) => Fractional (T a) Source 
(PseudoRing a, Real a, IntegerConstant a) => Num (T a) Source 
(Transcendental a, RationalConstant a) => C (T a) Source 
(Transcendental a, RationalConstant a) => C (T a) Source 
(Field a, RationalConstant a) => C (T a) Source 
(Real a, PseudoRing a, IntegerConstant a) => C (T a) Source 
(PseudoRing a, IntegerConstant a) => C (T a) Source 
Additive a => C (T a) Source

We do not require a numeric prelude superclass, thus also LLVM only types like vectors are instances.

Flatten (T a) Source 
(Real a, IntegerConstant a, (~) * a (Scalar a), PseudoModule a) => C (T a) (T a) Source 
(Real a, IntegerConstant a, (~) * a (Scalar a), PseudoModule a) => Sqr (T a) (T a) Source 
(Sqr (T a) (T v), RationalConstant a, Algebraic a) => C (T a) (T v) Source 
((~) * a (Scalar v), PseudoModule v, IntegerConstant a) => C (T a) (T v) Source 
type Registers (T a) = a Source 

decons :: T a -> forall r. CodeGenFunction r a Source

square :: PseudoRing a => T a -> T a Source

sqrt :: Algebraic a => T a -> T a Source

The same as sqrt, but needs only Algebraic constraint, not Transcendental.

max :: Real a => T a -> T a -> T a Source

min :: Real a => T a -> T a -> T a Source

limit :: Real a => (T a, T a) -> T a -> T a Source

fraction :: Fraction a => T a -> T a Source

(%==) :: CmpRet a => T (Value a) -> T (Value a) -> T (Value (CmpResult a)) infix 4 Source

(%/=) :: CmpRet a => T (Value a) -> T (Value a) -> T (Value (CmpResult a)) infix 4 Source

(%<) :: CmpRet a => T (Value a) -> T (Value a) -> T (Value (CmpResult a)) infix 4 Source

(%<=) :: CmpRet a => T (Value a) -> T (Value a) -> T (Value (CmpResult a)) infix 4 Source

(%>) :: CmpRet a => T (Value a) -> T (Value a) -> T (Value (CmpResult a)) infix 4 Source

(%>=) :: CmpRet a => T (Value a) -> T (Value a) -> T (Value (CmpResult a)) infix 4 Source

(%&&) :: T (Value Bool) -> T (Value Bool) -> T (Value Bool) infixr 3 Source

Lazy AND

(%||) :: T (Value Bool) -> T (Value Bool) -> T (Value Bool) infixr 2 Source

Lazy OR

(?) :: (Flatten value, Registers value ~ a, Phi a) => T (Value Bool) -> (value, value) -> value infix 0 Source

true ? (t,f) evaluates t, false ? (t,f) evaluates f. t and f can reuse interim results, but they cannot contribute shared results, since only one of them will be run. Cf. '(??)'

(??) :: (IsFirstClass a, CmpRet a) => T (Value (CmpResult a)) -> (T (Value a), T (Value a)) -> T (Value a) infix 0 Source

The expression c ?? (t,f) evaluates both t and f and selects components from t and f according to c. It is useful for vector values and for sharing t or f with other branches of an expression.

lift0 :: (forall r. CodeGenFunction r a) -> T a Source

lift1 :: (forall r. a -> CodeGenFunction r b) -> T a -> T b Source

lift2 :: (forall r. a -> b -> CodeGenFunction r c) -> T a -> T b -> T c Source

lift3 :: (forall r. a -> b -> c -> CodeGenFunction r d) -> T a -> T b -> T c -> T d Source

unlift0 :: Flatten value => value -> forall r. CodeGenFunction r (Registers value) Source

unlift1 :: Flatten value => (T a -> value) -> forall r. a -> CodeGenFunction r (Registers value) Source

unlift2 :: Flatten value => (T a -> T b -> value) -> forall r. a -> b -> CodeGenFunction r (Registers value) Source

unlift3 :: Flatten value => (T a -> T b -> T c -> value) -> forall r. a -> b -> c -> CodeGenFunction r (Registers value) Source

unlift4 :: Flatten value => (T a -> T b -> T c -> T d -> value) -> forall r. a -> b -> c -> d -> CodeGenFunction r (Registers value) Source

unlift5 :: Flatten value => (T a -> T b -> T c -> T d -> T e -> value) -> forall r. a -> b -> c -> d -> e -> CodeGenFunction r (Registers value) Source

constant :: IsConst a => a -> T (Value a) Source

class Flatten value where Source

Associated Types

type Registers value :: * Source

Methods

flattenCode :: value -> Compute r (Registers value) Source

unfoldCode :: T (Registers value) -> value Source

flatten :: Flatten value => value -> CodeGenFunction r (Registers value) Source

unfold :: Flatten value => Registers value -> value Source

flattenCodeTraversable :: (Flatten value, Traversable f) => f value -> Compute r (f (Registers value)) Source

unfoldCodeTraversable :: (Flatten value, Traversable f, Applicative f) => T (f (Registers value)) -> f value Source