llvm-extra-0.10: Utility functions for the llvm interface

Safe HaskellNone

LLVM.Extra.Multi.Value

Synopsis

Documentation

newtype T a Source

Constructors

Cons (ValueOf a) 

Instances

C T 
C a => Zero (T a) 
C a => Undefined (T a) 
C a => Phi (T a) 
Select a => Select (T a) 
Transcendental a => Transcendental (T a) 
Algebraic a => Algebraic (T a) 
Logic a => Logic (T a) 
FloatingComparison a => FloatingComparison (T a) 
Comparison a => Comparison (T a) 
Fraction a => Fraction (T a) 
Real a => Real (T a) 
RationalConstant a => RationalConstant (T a) 
Field a => Field (T a) 
IntegerConstant a => IntegerConstant (T a) 
PseudoModule a => PseudoModule (T a) 
PseudoRing a => PseudoRing (T a) 
Additive a => Additive (T a) 
Compose (T a) 
(C a, C (ValueOf a)) => C (T a) 

class C a whereSource

Methods

cons :: a -> T aSource

undef :: T aSource

zero :: T aSource

phi :: BasicBlock -> T a -> CodeGenFunction r (T a)Source

addPhi :: BasicBlock -> T a -> T a -> CodeGenFunction r ()Source

Instances

C Bool 
C Double 
C Float 
C Int 
C Int8 
C Int16 
C Int32 
C Int64 
C Word 
C Word8 
C Word16 
C Word32 
C Word64 
C () 
C Bool8 
C (StablePtr a) 
C (Ptr a) 
IsFunction a => C (FunPtr a) 
C a => C (Complex a) 
C a => C (Maybe a) 
Positive n => C (IntN n) 
IsType a => C (Ptr a) 
Positive n => C (WordN n) 
C tuple => C (Tuple tuple) 
(C a, C b) => C (a, b) 
(IsInteger w, IsConst w) => C (T w i) 
(Positive n, C a) => C (Vector n a) 
(IsInteger w, IsConst w, Num w, Enum e) => C (T w e) 
C a => C (Tagged tag a) 
MultiValue a => C (Number flags a) 
(C a, C b, C c) => C (a, b, c) 
(C a, C b, C c, C d) => C (a, b, c, d) 

consPrimitive :: (IsConst al, Value al ~ ValueOf a) => al -> T aSource

undefPrimitive :: (IsType al, Value al ~ ValueOf a) => T aSource

zeroPrimitive :: (IsType al, Value al ~ ValueOf a) => T aSource

phiPrimitive :: (IsFirstClass al, Value al ~ ValueOf a) => BasicBlock -> T a -> CodeGenFunction r (T a)Source

addPhiPrimitive :: (IsFirstClass al, Value al ~ ValueOf a) => BasicBlock -> T a -> T a -> CodeGenFunction r ()Source

consTuple :: Value a => a -> T aSource

undefTuple :: (Value a, ValueOf a ~ al, Undefined al) => T aSource

zeroTuple :: (Value a, ValueOf a ~ al, Zero al) => T aSource

phiTuple :: (Value a, ValueOf a ~ al, Phi al) => BasicBlock -> T a -> CodeGenFunction r (T a)Source

addPhiTuple :: (Value a, ValueOf a ~ al, Phi al) => BasicBlock -> T a -> T a -> CodeGenFunction r ()Source

consUnit :: ValueOf a ~ () => a -> T aSource

toEnum :: ValueOf w ~ Value w => T w -> T (T w e)Source

fromEnum :: ValueOf w ~ Value w => T (T w e) -> T wSource

succ :: (IsArithmetic w, IntegerConstant w) => T (T w e) -> CodeGenFunction r (T (T w e))Source

pred :: (IsArithmetic w, IntegerConstant w) => T (T w e) -> CodeGenFunction r (T (T w e))Source

cmpEnum :: (CmpRet w, IsPrimitive w) => CmpPredicate -> T (T w a) -> T (T w a) -> CodeGenFunction r (T Bool)Source

class C a => Bounded a whereSource

Instances

(IsInteger w, IsConst w, Num w, Enum e, Bounded e) => Bounded (T w e) 

splitMaybe :: T (Maybe a) -> (T Bool, T a)Source

toMaybe :: T Bool -> T a -> T (Maybe a)Source

nothing :: C a => T (Maybe a)Source

just :: T a -> T (Maybe a)Source

fst :: T (a, b) -> T aSource

snd :: T (a, b) -> T bSource

curry :: (T (a, b) -> c) -> T a -> T b -> cSource

uncurry :: (T a -> T b -> c) -> T (a, b) -> cSource

mapFst :: (T a0 -> T a1) -> T (a0, b) -> T (a1, b)Source

mapSnd :: (T b0 -> T b1) -> T (a, b0) -> T (a, b1)Source

mapFstF :: Functor f => (T a0 -> f (T a1)) -> T (a0, b) -> f (T (a1, b))Source

mapSndF :: Functor f => (T b0 -> f (T b1)) -> T (a, b0) -> f (T (a, b1))Source

swap :: T (a, b) -> T (b, a)Source

fst3 :: T (a, b, c) -> T aSource

snd3 :: T (a, b, c) -> T bSource

thd3 :: T (a, b, c) -> T cSource

mapFst3 :: (T a0 -> T a1) -> T (a0, b, c) -> T (a1, b, c)Source

mapSnd3 :: (T b0 -> T b1) -> T (a, b0, c) -> T (a, b1, c)Source

mapThd3 :: (T c0 -> T c1) -> T (a, b, c0) -> T (a, b, c1)Source

mapFst3F :: Functor f => (T a0 -> f (T a1)) -> T (a0, b, c) -> f (T (a1, b, c))Source

mapSnd3F :: Functor f => (T b0 -> f (T b1)) -> T (a, b0, c) -> f (T (a, b1, c))Source

mapThd3F :: Functor f => (T c0 -> f (T c1)) -> T (a, b, c0) -> f (T (a, b, c1))Source

zip :: T a -> T b -> T (a, b)Source

zip3 :: T a -> T b -> T c -> T (a, b, c)Source

zip4 :: T a -> T b -> T c -> T d -> T (a, b, c, d)Source

unzip :: T (a, b) -> (T a, T b)Source

unzip3 :: T (a, b, c) -> (T a, T b, T c)Source

unzip4 :: T (a, b, c, d) -> (T a, T b, T c, T d)Source

tuple :: T tuple -> T (Tuple tuple)Source

untuple :: T (Tuple tuple) -> T tupleSource

tag :: T a -> T (Tagged tag a)Source

untag :: T (Tagged tag a) -> T aSource

liftTaggedM :: Monad m => (T a -> m (T b)) -> T (Tagged tag a) -> m (T (Tagged tag b))Source

liftTaggedM2 :: Monad m => (T a -> T b -> m (T c)) -> T (Tagged tag a) -> T (Tagged tag b) -> m (T (Tagged tag c))Source

consComplex :: T a -> T a -> T (Complex a)Source

deconsComplex :: T (Complex a) -> (T a, T a)Source

class Compose multituple whereSource

Associated Types

type Composed multituple Source

Methods

compose :: multituple -> T (Composed multituple)Source

A nested zip.

Instances

Compose () 
Compose a => Compose (Complex a) 
Compose tuple => Compose (Tuple tuple) 
Compose (T a) 
(Compose a, Compose b) => Compose (a, b) 
Compose a => Compose (Tagged tag a) 
(Flags flags, Compose a) => Compose (Number flags a) 
(Compose a, Compose b, Compose c) => Compose (a, b, c) 
(Compose a, Compose b, Compose c, Compose d) => Compose (a, b, c, d) 

class Composed (Decomposed T pattern) ~ PatternTuple pattern => Decompose pattern whereSource

Methods

decompose :: pattern -> T (PatternTuple pattern) -> Decomposed T patternSource

A nested unzip. Since it is not obvious how deep to decompose nested tuples, you must provide a pattern of the decomposed tuple. E.g.

 f :: MultiValue ((a,b),(c,d)) ->
      ((MultiValue a, MultiValue b), MultiValue (c,d))
 f = decompose ((atom,atom),atom)

Instances

Decompose () 
Decompose pa => Decompose (Complex pa) 
Decompose p => Decompose (Tuple p) 
Decompose (Atom a) 
(Decompose pa, Decompose pb) => Decompose (pa, pb) 
Decompose pa => Decompose (Tagged tag pa) 
(Flags flags, Decompose pa) => Decompose (Number flags pa) 
(Decompose pa, Decompose pb, Decompose pc) => Decompose (pa, pb, pc) 
(Decompose pa, Decompose pb, Decompose pc, Decompose pd) => Decompose (pa, pb, pc, pd) 

type family Decomposed f pattern Source

type family PatternTuple pattern Source

modify :: (Compose a, Decompose pattern) => pattern -> (Decomposed T pattern -> a) -> T (PatternTuple pattern) -> T (Composed a)Source

A combination of compose and decompose that let you operate on tuple multivalues as Haskell tuples.

modify2 :: (Compose a, Decompose patternA, Decompose patternB) => patternA -> patternB -> (Decomposed T patternA -> Decomposed T patternB -> a) -> T (PatternTuple patternA) -> T (PatternTuple patternB) -> T (Composed a)Source

modifyF :: (Compose a, Decompose pattern, Functor f) => pattern -> (Decomposed T pattern -> f a) -> T (PatternTuple pattern) -> f (T (Composed a))Source

modifyF2 :: (Compose a, Decompose patternA, Decompose patternB, Functor f) => patternA -> patternB -> (Decomposed T patternA -> Decomposed T patternB -> f a) -> T (PatternTuple patternA) -> T (PatternTuple patternB) -> f (T (Composed a))Source

data Atom a Source

Constructors

Atom 

Instances

lift1 :: (ValueOf a -> ValueOf b) -> T a -> T bSource

liftM0 :: Monad m => m (ValueOf a) -> m (T a)Source

liftM :: Monad m => (ValueOf a -> m (ValueOf b)) -> T a -> m (T b)Source

liftM2 :: Monad m => (ValueOf a -> ValueOf b -> m (ValueOf c)) -> T a -> T b -> m (T c)Source

liftM3 :: Monad m => (ValueOf a -> ValueOf b -> ValueOf c -> m (ValueOf d)) -> T a -> T b -> T c -> m (T d)Source

class C a => Additive a whereSource

Methods

add :: T a -> T a -> CodeGenFunction r (T a)Source

sub :: T a -> T a -> CodeGenFunction r (T a)Source

neg :: T a -> CodeGenFunction r (T a)Source

class PseudoRing a => Field a whereSource

Methods

fdiv :: T a -> T a -> CodeGenFunction r (T a)Source

Instances

Field Double 
Field Float 
Field a => Field (Tagged tag a) 
(Flags flags, MultiValue a, Field a) => Field (Number flags a) 

type family Scalar vector :: *Source

class (PseudoRing (Scalar v), Additive v) => PseudoModule v whereSource

Methods

scale :: T (Scalar v) -> T v -> CodeGenFunction r (T v)Source

class Additive a => Real a whereSource

Methods

min :: T a -> T a -> CodeGenFunction r (T a)Source

max :: T a -> T a -> CodeGenFunction r (T a)Source

abs :: T a -> CodeGenFunction r (T a)Source

signum :: T a -> CodeGenFunction r (T a)Source

Instances

Real Double 
Real Float 
Real Int 
Real Int8 
Real Int16 
Real Int32 
Real Int64 
Real Word 
Real Word8 
Real Word16 
Real Word32 
Real Word64 
Positive n => Real (IntN n) 
Positive n => Real (WordN n) 
Real a => Real (Tagged tag a) 
(Flags flags, MultiValue a, Real a) => Real (Number flags a) 

class Real a => Fraction a whereSource

Instances

class (ValueOf a ~ Value ar, IsFloating ar, RationalConstant ar, CmpRet ar, IsPrimitive ar) => NativeFloating a ar Source

class Field a => Algebraic a whereSource

Methods

sqrt :: T a -> CodeGenFunction r (T a)Source

Instances

class C a => Select a whereSource

Methods

select :: T Bool -> T a -> T a -> CodeGenFunction r (T a)Source

class Real a => Comparison a whereSource

Methods

cmp :: CmpPredicate -> T a -> T a -> CodeGenFunction r (T Bool)Source

It must hold

 max x y  ==  do gt <- cmp CmpGT x y; select gt x y

class C a => Logic a whereSource

Methods

and :: T a -> T a -> CodeGenFunction r (T a)Source

or :: T a -> T a -> CodeGenFunction r (T a)Source

xor :: T a -> T a -> CodeGenFunction r (T a)Source

inv :: T a -> CodeGenFunction r (T a)Source

Instances

Logic Bool 
Logic Word8 
Logic Word16 
Logic Word32 
Logic Word64 
Logic Bool8 
Positive n => Logic (WordN n) 
(IsInteger w, IsConst w) => Logic (T w i) 
(Positive n, Logic a) => Logic (Vector n a) 
Logic a => Logic (Tagged tag a)