Safe Haskell | None |
---|
LLVM.Extra.Arithmetic
Contents
- class Zero a => Additive a where
- zero :: a
- add :: a -> a -> CodeGenFunction r a
- sub :: a -> a -> CodeGenFunction r a
- neg :: a -> CodeGenFunction r a
- one :: IntegerConstant a => a
- inc :: (IsArithmetic a, IsConst a, Num a) => Value a -> CodeGenFunction r (Value a)
- dec :: (IsArithmetic a, IsConst a, Num a) => Value a -> CodeGenFunction r (Value a)
- class Additive a => PseudoRing a where
- mul :: a -> a -> CodeGenFunction r a
- square :: PseudoRing a => a -> CodeGenFunction r a
- class (PseudoRing a, Additive v) => PseudoModule a v where
- scale :: a -> v -> CodeGenFunction r v
- class PseudoRing a => Field a where
- fdiv :: a -> a -> CodeGenFunction r a
- class IntegerConstant a where
- fromInteger' :: Integer -> a
- class IntegerConstant a => RationalConstant a where
- fromRational' :: Rational -> a
- idiv :: IsInteger a => Value a -> Value a -> CodeGenFunction r (Value a)
- irem :: IsInteger a => Value a -> Value a -> CodeGenFunction r (Value a)
- fcmp :: (IsFloating a, CmpRet a, CmpResult a ~ b) => FPPredicate -> Value a -> Value a -> CodeGenFunction r (Value b)
- cmp :: (CmpRet a, CmpResult a ~ b) => CmpPredicate -> Value a -> Value a -> CodeGenFunction r (Value b)
- data CmpPredicate
- and :: IsInteger a => Value a -> Value a -> CodeGenFunction r (Value a)
- or :: IsInteger a => Value a -> Value a -> CodeGenFunction r (Value a)
- class Additive a => Real a where
- min :: a -> a -> CodeGenFunction r a
- max :: a -> a -> CodeGenFunction r a
- abs :: a -> CodeGenFunction r a
- signum :: a -> CodeGenFunction r a
- class Real a => Fraction a where
- truncate :: a -> CodeGenFunction r a
- fraction :: a -> CodeGenFunction r a
- signedFraction :: Fraction a => a -> CodeGenFunction r a
- addToPhase :: Fraction a => a -> a -> CodeGenFunction r a
- incPhase :: Fraction a => a -> a -> CodeGenFunction r a
- advanceArrayElementPtr :: Value (Ptr a) -> CodeGenFunction r (Value (Ptr a))
- class Field a => Algebraic a where
- sqrt :: a -> CodeGenFunction r a
- class Algebraic a => Transcendental a where
- pi :: CodeGenFunction r a
- sin, log, exp, cos :: a -> CodeGenFunction r a
- pow :: a -> a -> CodeGenFunction r a
arithmetic: generalized and improved type inference
class Zero a => Additive a whereSource
This and the following type classes are intended for arithmetic operations on wrappers around LLVM types. E.g. you might define a fixed point fraction type by
newtype Fixed = Fixed Int32
and then use the same methods for floating point and fixed point arithmetic.
In contrast to the arithmetic methods in the llvm
wrapper,
in our methods the types of operands and result match.
Advantage: Type inference determines most of the types automatically.
Disadvantage: You cannot use constant values directly,
but you have to convert them all to Value
.
Methods
add :: a -> a -> CodeGenFunction r aSource
sub :: a -> a -> CodeGenFunction r aSource
neg :: a -> CodeGenFunction r aSource
Instances
IsArithmetic a => Additive (Value a) | |
IsArithmetic a => Additive (ConstValue a) | |
(Additive a, Additive b) => Additive (a, b) | |
(Additive a, Additive b, Additive c) => Additive (a, b, c) |
one :: IntegerConstant a => aSource
inc :: (IsArithmetic a, IsConst a, Num a) => Value a -> CodeGenFunction r (Value a)Source
dec :: (IsArithmetic a, IsConst a, Num a) => Value a -> CodeGenFunction r (Value a)Source
class Additive a => PseudoRing a whereSource
Methods
mul :: a -> a -> CodeGenFunction r aSource
Instances
IsArithmetic v => PseudoRing (Value v) | |
IsArithmetic v => PseudoRing (ConstValue v) |
square :: PseudoRing a => a -> CodeGenFunction r aSource
class (PseudoRing a, Additive v) => PseudoModule a v whereSource
Methods
scale :: a -> v -> CodeGenFunction r vSource
Instances
PseudoModule a v => PseudoModule (Value a) (Value v) | |
PseudoModule a v => PseudoModule (ConstValue a) (ConstValue v) |
class PseudoRing a => Field a whereSource
Methods
fdiv :: a -> a -> CodeGenFunction r aSource
Instances
IsFloating v => Field (Value v) | |
IsFloating v => Field (ConstValue v) |
class IntegerConstant a whereSource
Methods
fromInteger' :: Integer -> aSource
Instances
IntegerConstant a => IntegerConstant (Value a) | |
IntegerConstant a => IntegerConstant (ConstValue a) |
class IntegerConstant a => RationalConstant a whereSource
Methods
fromRational' :: Rational -> aSource
Instances
RationalConstant a => RationalConstant (Value a) | |
RationalConstant a => RationalConstant (ConstValue a) |
fcmp :: (IsFloating a, CmpRet a, CmpResult a ~ b) => FPPredicate -> Value a -> Value a -> CodeGenFunction r (Value b)Source
cmp :: (CmpRet a, CmpResult a ~ b) => CmpPredicate -> Value a -> Value a -> CodeGenFunction r (Value b)Source
data CmpPredicate
class Additive a => Real a whereSource
Methods
min :: a -> a -> CodeGenFunction r aSource
max :: a -> a -> CodeGenFunction r aSource
abs :: a -> CodeGenFunction r aSource
signum :: a -> CodeGenFunction r aSource
signedFraction :: Fraction a => a -> CodeGenFunction r aSource
addToPhase :: Fraction a => a -> a -> CodeGenFunction r aSource
incPhase :: Fraction a => a -> a -> CodeGenFunction r aSource
both increment and phase must be non-negative
pointer arithmetic
advanceArrayElementPtr :: Value (Ptr a) -> CodeGenFunction r (Value (Ptr a))Source
transcendental functions
class Field a => Algebraic a whereSource
Methods
sqrt :: a -> CodeGenFunction r aSource
Instances
IsFloating a => Algebraic (Value a) |
class Algebraic a => Transcendental a whereSource
Methods
pi :: CodeGenFunction r aSource
sin, log, exp, cos :: a -> CodeGenFunction r aSource
pow :: a -> a -> CodeGenFunction r aSource
Instances
(IsFloating a, TranscendentalConstant a) => Transcendental (Value a) |