llvm-tf-3.0.3.1.6: Bindings to the LLVM compiler toolkit using type families.

Safe HaskellNone
LanguageHaskell98

LLVM.Util.Arithmetic

Synopsis

Documentation

type TValue r a = CodeGenFunction r (Value a) Source

Synonym for CodeGenFunction r (Value a).

(%==) :: CmpRet a => TValue r a -> TValue r a -> TValue r (CmpResult a) infix 4 Source

Comparison functions.

(%/=) :: CmpRet a => TValue r a -> TValue r a -> TValue r (CmpResult a) infix 4 Source

Comparison functions.

(%<) :: CmpRet a => TValue r a -> TValue r a -> TValue r (CmpResult a) infix 4 Source

Comparison functions.

(%<=) :: CmpRet a => TValue r a -> TValue r a -> TValue r (CmpResult a) infix 4 Source

Comparison functions.

(%>) :: CmpRet a => TValue r a -> TValue r a -> TValue r (CmpResult a) infix 4 Source

Comparison functions.

(%>=) :: CmpRet a => TValue r a -> TValue r a -> TValue r (CmpResult a) infix 4 Source

Comparison functions.

(%&&) :: TValue r Bool -> TValue r Bool -> TValue r Bool infixr 3 Source

Lazy and.

(%||) :: TValue r Bool -> TValue r Bool -> TValue r Bool infixr 2 Source

Lazy or.

(?) :: IsFirstClass a => TValue r Bool -> (TValue r a, TValue r a) -> TValue r a infix 0 Source

Conditional, returns first element of the pair when condition is true, otherwise second.

(??) :: (IsFirstClass a, CmpRet a) => TValue r (CmpResult a) -> (TValue r a, TValue r a) -> TValue r a infix 0 Source

retrn :: Ret (Value a) r => TValue r a -> CodeGenFunction r () Source

Return a value from an arithFunction.

set :: TValue r a -> CodeGenFunction r (TValue r a) Source

Use x <- set $ ... to make a binding.

class ArithFunction r z a b | a -> b r z, b r z -> a Source

Minimal complete definition

arithFunction'

Instances

ArithFunction r z b0 b1 => ArithFunction r z (CodeGenFunction r a -> b0) (a -> b1) 
Ret a r => ArithFunction r a (CodeGenFunction r a) (CodeGenFunction r ()) 

arithFunction :: ArithFunction r z a b => a -> b Source

Unlift a function with TValue to have Value arguments.

class ToArithFunction r a b | a r -> b, b -> a r Source

Minimal complete definition

toArithFunction'

Instances

ToArithFunction r (IO b) (CodeGenFunction r (Value b)) 
ToArithFunction r b0 b1 => ToArithFunction r (a -> b0) (CodeGenFunction r (Value a) -> b1) 

toArithFunction :: ToArithFunction r f g => Function f -> g Source

Lift a function from having Value arguments to having TValue arguments.

recursiveFunction :: (IsFunction f, FunctionArgs f, code ~ FunctionCodeGen f, ArithFunction r1 z arith code, ToArithFunction r0 f g) => (g -> arith) -> CodeGenModule (Function f) Source

Define a recursive arithFunction, gets passed itself as the first argument.

class CallIntrinsic a Source

Minimal complete definition

callIntrinsic1', callIntrinsic2'