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

LLVM.DSL.Value

Description

Wrap LLVM code for arithmetic computations. Similar to LLVM.DSL.Expression but not based on MultiValue but on LLVM.Extra.Arithmetic methods. Detects sharing using a Vault.

Synopsis

Documentation

data T a Source #

Instances

Instances details
Applicative T Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

pure :: a -> T a #

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

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

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

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

Functor T Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

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

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

(Additive a, IntegerConstant a) => Enum (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

succ :: T a -> T a #

pred :: T a -> T a #

toEnum :: Int -> T a #

fromEnum :: T a -> Int #

enumFrom :: T a -> [T a] #

enumFromThen :: T a -> T a -> [T a] #

enumFromTo :: T a -> T a -> [T a] #

enumFromThenTo :: T a -> T a -> T a -> [T a] #

(Transcendental a, Real a, RationalConstant a) => Floating (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

pi :: T a #

exp :: T a -> T a #

log :: T a -> T a #

sqrt :: T a -> T a #

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

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

sin :: T a -> T a #

cos :: T a -> T a #

tan :: T a -> T a #

asin :: T a -> T a #

acos :: T a -> T a #

atan :: T a -> T a #

sinh :: T a -> T a #

cosh :: T a -> T a #

tanh :: T a -> T a #

asinh :: T a -> T a #

acosh :: T a -> T a #

atanh :: T a -> T a #

log1p :: T a -> T a #

expm1 :: T a -> T a #

log1pexp :: T a -> T a #

log1mexp :: T a -> T a #

(PseudoRing a, Real a, IntegerConstant a) => Num (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

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

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

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

negate :: T a -> T a #

abs :: T a -> T a #

signum :: T a -> T a #

fromInteger :: Integer -> T a #

(Field a, Real a, RationalConstant a) => Fractional (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

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

recip :: T a -> T a #

fromRational :: Rational -> T a #

Flatten (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Associated Types

type Registers (T a) Source #

Methods

flattenCode :: T a -> Compute r (Registers (T a)) Source #

unfoldCode :: T (Registers (T a)) -> T a Source #

(Real a, PseudoRing a, IntegerConstant a) => C (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

abs :: T a -> T a #

signum :: T a -> T a #

Additive a => C (T a) Source #

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

Instance details

Defined in LLVM.DSL.Value

Methods

zero :: T a #

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

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

negate :: T a -> T a #

(Transcendental a, RationalConstant a) => C (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

sqrt :: T a -> T a #

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

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

(Field a, RationalConstant a) => C (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

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

recip :: T a -> T a #

fromRational' :: Rational -> T a #

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

(PseudoRing a, IntegerConstant a) => C (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

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

one :: T a #

fromInteger :: Integer -> T a #

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

(Transcendental a, RationalConstant a) => C (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

pi :: T a #

exp :: T a -> T a #

log :: T a -> T a #

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

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

sin :: T a -> T a #

cos :: T a -> T a #

tan :: T a -> T a #

asin :: T a -> T a #

acos :: T a -> T a #

atan :: T a -> T a #

sinh :: T a -> T a #

cosh :: T a -> T a #

tanh :: T a -> T a #

asinh :: T a -> T a #

acosh :: T a -> T a #

atanh :: T a -> T a #

(a ~ Scalar v, PseudoModule v, IntegerConstant a) => C (T a) (T v) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

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

(Sqr (T a) (T v), RationalConstant a, Algebraic a) => C (T a) (T v) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

norm :: T v -> T a #

(Real a, IntegerConstant a, a ~ Scalar a, PseudoModule a) => Sqr (T a) (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

normSqr :: T a -> T a #

(Real a, IntegerConstant a, a ~ Scalar a, PseudoModule a) => C (T a) (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Methods

norm :: T a -> T a #

type Registers (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

type Registers (T a) = a

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 #

Methods

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

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

Instances

Instances details
Flatten () Source # 
Instance details

Defined in LLVM.DSL.Value

Associated Types

type Registers () Source #

Methods

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

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

Flatten (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Associated Types

type Registers (T a) Source #

Methods

flattenCode :: T a -> Compute r (Registers (T a)) Source #

unfoldCode :: T (Registers (T a)) -> T a Source #

Flatten a => Flatten (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

Associated Types

type Registers (T a) Source #

Methods

flattenCode :: T a -> Compute r (Registers (T a)) Source #

unfoldCode :: T0 (Registers (T a)) -> T a Source #

(Flatten a, Flatten b) => Flatten (a, b) Source # 
Instance details

Defined in LLVM.DSL.Value

Associated Types

type Registers (a, b) Source #

Methods

flattenCode :: (a, b) -> Compute r (Registers (a, b)) Source #

unfoldCode :: T (Registers (a, b)) -> (a, b) Source #

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

Defined in LLVM.DSL.Value

Associated Types

type Registers (a, b, c) Source #

Methods

flattenCode :: (a, b, c) -> Compute r (Registers (a, b, c)) Source #

unfoldCode :: T (Registers (a, b, c)) -> (a, b, c) Source #

type family Registers value Source #

Instances

Instances details
type Registers () Source # 
Instance details

Defined in LLVM.DSL.Value

type Registers () = ()
type Registers (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

type Registers (T a) = a
type Registers (T a) Source # 
Instance details

Defined in LLVM.DSL.Value

type Registers (T a) = T (Registers a)
type Registers (a, b) Source # 
Instance details

Defined in LLVM.DSL.Value

type Registers (a, b) = (Registers a, Registers b)
type Registers (a, b, c) Source # 
Instance details

Defined in LLVM.DSL.Value

type Registers (a, b, c) = (Registers a, Registers b, Registers c)

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 #