knead-0.2: Repa array processing using LLVM JIT

Safe HaskellNone

Data.Array.Knead.Parameter

Synopsis

Documentation

data T p a Source

This data type is for parameters of parameterized signal generators and causal processes. It is better than using plain functions of type p -> a since it allows for numeric instances and we can make explicit, whether a parameter is constant.

We recommend to use parameters for atomic types. Although a parameter of type T p (a,b) is possible, it means that the whole parameter is variable if only one of the pair elements is variable. This way you may miss optimizations.

Constructors

Constant a 
Variable (p -> a) 

Instances

Arrow T

arr is useful for lifting parameter selectors to our parameter type without relying on the constructor.

Category T

. can be used for fetching a parameter from a super-parameter.

Monad (T p) 
Functor (T p)

Useful for splitting T p (a,b) into T p a and T p b using fmap fst and fmap snd.

Applicative (T p)

Useful for combining T p a and T p b to T p (a,b) using liftA2 (,). However, we do not recommend to do so because the result parameter can only be constant if both operands are constant.

Fractional a => Fractional (T p a) 
Num a => Num (T p a) 

get :: T p a -> p -> aSource

valueTuple :: (MakeValueTuple tuple, ValueTuple tuple ~ value) => T p tuple -> value -> valueSource

The call value param v requires that v represents the same value as valueTupleOf (get param p) for some p. However v might be the result of a load operation and param might be a constant. In this case it is more efficient to use valueTupleOf (get param undefined) since the constant is translated to an LLVM constant that allows for certain optimizations.

This is the main function for taking advantage of a constant parameter in low-level implementations. For simplicity we do not omit constant parameters in the parameter struct since this would mean to construct types at runtime and might become ugly. Instead we just check using value at the according places in LLVM code whether a parameter is constant and ignore the parameter from the struct in this case. In many cases there will be no speed benefit because the parameter will be loaded to a register anyway. It can only lead to speed-up if subsequent optimizations can precompute constant expressions. Another example is drop where a loop with constant loop count can be generated. For small loop counts and simple loop bodies the loop might get unrolled.

multiValue :: C a => T p a -> T a -> T aSource

genericValue :: (a -> value) -> T p a -> value -> valueSource

withTuple :: (Storable tuple, MakeValueTuple tuple, ValueTuple tuple ~ value, C value) => T p tuple -> (forall parameters. (Storable parameters, MakeValueTuple parameters, C (ValueTuple parameters)) => (p -> parameters) -> (ValueTuple parameters -> value) -> a) -> aSource

This function provides specialised variants of get and value, that use the unit type for constants and thus save space in parameter structures.

withMulti :: (Storable b, C b) => T p b -> (forall parameters. (Storable parameters, C parameters) => (p -> parameters) -> (T parameters -> T b) -> a) -> aSource

with :: (Storable b, C b) => (b -> T b) -> T p b -> (forall parameters. (Storable parameters, C parameters) => (p -> parameters) -> (T parameters -> T b) -> a) -> aSource

data Tunnel p a Source

Constructors

forall t . (Storable t, C t) => Tunnel (p -> t) (T t -> T a) 

tunnel :: (Storable a, C a) => (a -> T a) -> T p a -> Tunnel p aSource

($#) :: (T p a -> b) -> a -> bSource