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

Safe HaskellNone

LLVM.Extra.Multi.Value

Synopsis

Documentation

newtype T a Source

Constructors

Cons (Repr Value a) 

Instances

C T 
C a => Phi (T a) 
Select a => Select (T a) 
C a => Zero (T a) 
C a => Undefined (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 (T a) 

class C a whereSource

Associated Types

type Repr f a :: *Source

Methods

cons :: a -> T aSource

undef :: T aSource

zero :: T aSource

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

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

Instances

C Bool 
C Double 
C Float 
C Int8 
C Int16 
C Int32 
C Int64 
C Word8 
C Word16 
C Word32 
C Word64 
C () 
C (StablePtr a) 
IsType a => C (Ptr a) 
IsFunction a => C (FunPtr a) 
C a => C (Complex a) 
C a => C (Maybe a) 
(C a, C b) => C (a, b) 
(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 ~ Repr Value a) => al -> T aSource

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

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

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

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

consUnit :: Repr Value a ~ () => a -> T aSource

undefUnit :: Repr Value a ~ () => T aSource

zeroUnit :: Repr Value a ~ () => T aSource

phisUnit :: Repr Value a ~ () => BasicBlock -> T a -> CodeGenFunction r (T a)Source

addPhisUnit :: Repr Value a ~ () => BasicBlock -> T a -> T a -> CodeGenFunction r ()Source

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

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

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

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 (T a) 
(Compose a, Compose b) => Compose (a, b) 
(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 (Atom a) 
(Decompose pa, Decompose pb) => Decompose (pa, pb) 
(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 :: (Repr Value a -> Repr Value b) -> T a -> T bSource

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

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

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

liftM3 :: Monad m => (Repr Value a -> Repr Value b -> Repr Value c -> m (Repr Value 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

inc :: (Additive i, IntegerConstant i) => T i -> CodeGenFunction r (T i)Source

dec :: (Additive i, IntegerConstant i) => T i -> CodeGenFunction r (T i)Source

class PseudoRing a => Field a whereSource

Methods

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

Instances

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

class Real a => Fraction a whereSource

Methods

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

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

class (Repr Value a ~ Value ar, IsFloating ar, RationalConstant ar, CmpRet ar, NumberOfElements ar ~ D1, CmpResult ar ~ Bool) => NativeFloating a ar Source

truncateToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i)Source

roundToIntFast :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i)Source

ceilingToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i)Source

floorToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T i)Source

splitFractionToInt :: (NativeInteger i ir, NativeFloating a ar) => T a -> CodeGenFunction r (T (i, a))Source

class Field a => Algebraic a whereSource

Methods

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

class Algebraic a => Transcendental a whereSource

Methods

pi :: CodeGenFunction r (T a)Source

sin, log, exp, cos :: T a -> CodeGenFunction r (T a)Source

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

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 Comparison a => FloatingComparison a whereSource

Methods

fcmp :: FPPredicate -> T a -> T a -> CodeGenFunction r (T Bool)Source

class 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

class BitShift a whereSource

Methods

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

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

class PseudoRing a => Integral a whereSource

Methods

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

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

fromIntegral :: (NativeInteger i ir, NativeFloating a ar) => T i -> CodeGenFunction r (T a)Source