llvm-dsl-0.1.2: Support for writing an EDSL with LLVM-JIT as target
Safe HaskellSafe-Inferred
LanguageHaskell98

LLVM.DSL.Parameter

Synopsis

Documentation

data T p a Source #

This data type is for parameters of parameterized LLVM code. 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 opportunities for constant folding.

Instances

Instances details
Arrow T Source #

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

Instance details

Defined in LLVM.DSL.Parameter

Methods

arr :: (b -> c) -> T b c #

first :: T b c -> T (b, d) (c, d) #

second :: T b c -> T (d, b) (d, c) #

(***) :: T b c -> T b' c' -> T (b, b') (c, c') #

(&&&) :: T b c -> T b c' -> T b (c, c') #

Category T Source #

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

Instance details

Defined in LLVM.DSL.Parameter

Methods

id :: forall (a :: k). T a a #

(.) :: forall (b :: k) (c :: k) (a :: k). T b c -> T a b -> T a c #

Applicative (T p) Source #

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.

Instance details

Defined in LLVM.DSL.Parameter

Methods

pure :: a -> T p a #

(<*>) :: T p (a -> b) -> T p a -> T p b #

liftA2 :: (a -> b -> c) -> T p a -> T p b -> T p c #

(*>) :: T p a -> T p b -> T p b #

(<*) :: T p a -> T p b -> T p a #

Functor (T p) Source #

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

Instance details

Defined in LLVM.DSL.Parameter

Methods

fmap :: (a -> b) -> T p a -> T p b #

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

Monad (T p) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Methods

(>>=) :: T p a -> (a -> T p b) -> T p b #

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

return :: a -> T p a #

Floating a => Floating (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Methods

pi :: T p a #

exp :: T p a -> T p a #

log :: T p a -> T p a #

sqrt :: T p a -> T p a #

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

logBase :: T p a -> T p a -> T p a #

sin :: T p a -> T p a #

cos :: T p a -> T p a #

tan :: T p a -> T p a #

asin :: T p a -> T p a #

acos :: T p a -> T p a #

atan :: T p a -> T p a #

sinh :: T p a -> T p a #

cosh :: T p a -> T p a #

tanh :: T p a -> T p a #

asinh :: T p a -> T p a #

acosh :: T p a -> T p a #

atanh :: T p a -> T p a #

log1p :: T p a -> T p a #

expm1 :: T p a -> T p a #

log1pexp :: T p a -> T p a #

log1mexp :: T p a -> T p a #

Num a => Num (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Methods

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

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

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

negate :: T p a -> T p a #

abs :: T p a -> T p a #

signum :: T p a -> T p a #

fromInteger :: Integer -> T p a #

Fractional a => Fractional (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Methods

(/) :: T p a -> T p a -> T p a #

recip :: T p a -> T p a #

fromRational :: Rational -> T p a #

Tuple (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Associated Types

type Composed (T p a) Source #

type Source (T p a) Source #

Methods

decompose :: T (Source (T p a)) (Composed (T p a)) -> T p a Source #

C a => C (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Methods

zero :: T p a #

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

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

negate :: T p a -> T p a #

C a => C (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Methods

sqrt :: T p a -> T p a #

root :: Integer -> T p a -> T p a #

(^/) :: T p a -> Rational -> T p a #

C a => C (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Methods

(/) :: T p a -> T p a -> T p a #

recip :: T p a -> T p a #

fromRational' :: Rational -> T p a #

(^-) :: T p a -> Integer -> T p a #

C a => C (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Methods

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

one :: T p a #

fromInteger :: Integer -> T p a #

(^) :: T p a -> Integer -> T p a #

C a => C (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Methods

pi :: T p a #

exp :: T p a -> T p a #

log :: T p a -> T p a #

logBase :: T p a -> T p a -> T p a #

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

sin :: T p a -> T p a #

cos :: T p a -> T p a #

tan :: T p a -> T p a #

asin :: T p a -> T p a #

acos :: T p a -> T p a #

atan :: T p a -> T p a #

sinh :: T p a -> T p a #

cosh :: T p a -> T p a #

tanh :: T p a -> T p a #

asinh :: T p a -> T p a #

acosh :: T p a -> T p a #

atanh :: T p a -> T p a #

type Composed (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

type Composed (T p a) = a
type Source (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

type Source (T p a) = p

($#) :: (T p a -> b) -> a -> b infixl 0 Source #

get :: T p a -> p -> a Source #

valueTuple :: (Value tuple, ValueOf tuple ~ value) => T p tuple -> value -> value Source #

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 a Source #

with :: C b => (b -> T b) -> T p b -> (forall parameters. C parameters => (p -> parameters) -> (T parameters -> T b) -> a) -> a Source #

withValue :: (C tuple, ValueOf tuple ~ value) => T p tuple -> (forall parameters. C parameters => (p -> parameters) -> (ValueOf parameters -> value) -> a) -> a Source #

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

withMulti :: C b => T p b -> (forall parameters. C parameters => (p -> parameters) -> (T parameters -> T b) -> a) -> a Source #

data Tunnel p a Source #

Constructors

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

tunnel :: C a => (a -> T a) -> T p a -> Tunnel p a Source #

class Tuple tuple where Source #

Associated Types

type Composed tuple Source #

type Source tuple Source #

Methods

decompose :: T (Source tuple) (Composed tuple) -> tuple Source #

Instances

Instances details
Tuple (T p a) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Associated Types

type Composed (T p a) Source #

type Source (T p a) Source #

Methods

decompose :: T (Source (T p a)) (Composed (T p a)) -> T p a Source #

(Tuple a, Tuple b, Source a ~ Source b) => Tuple (a, b) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Associated Types

type Composed (a, b) Source #

type Source (a, b) Source #

Methods

decompose :: T (Source (a, b)) (Composed (a, b)) -> (a, b) Source #

(Tuple a, Tuple b, Tuple c, Source a ~ Source b, Source b ~ Source c) => Tuple (a, b, c) Source # 
Instance details

Defined in LLVM.DSL.Parameter

Associated Types

type Composed (a, b, c) Source #

type Source (a, b, c) Source #

Methods

decompose :: T (Source (a, b, c)) (Composed (a, b, c)) -> (a, b, c) Source #

withTuple :: (Tuple tuple, Source tuple ~ p, Composed tuple ~ p) => (tuple -> f p) -> f p Source #

Provide all elements of a nested tuple as separate parameters.

If you do not use one of the tuple elements, you will get a type error like Couldn't match type `Param.Composed t0' with Int. The problem is that the type checker cannot infer that an element is a Parameter.T if it remains unused.

withTuple1 :: (Tuple tuple, Source tuple ~ p, Composed tuple ~ p) => (tuple -> f p a) -> f p a Source #

withTuple2 :: (Tuple tuple, Source tuple ~ p, Composed tuple ~ p) => (tuple -> f p a b) -> f p a b Source #

for implementation of new processes

wordInt :: T p Int -> T p Word Source #