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
- type family Scalar vector :: *
- class (PseudoRing (Scalar v), Additive v) => PseudoModule v where
- scale :: Scalar v -> 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)
- class Comparison a => FloatingComparison a where
- fcmp :: FPPredicate -> a -> a -> CodeGenFunction r (CmpResult a)
- class Comparison a where
- type CmpResult a :: *
- cmp :: CmpPredicate -> a -> a -> CodeGenFunction r (CmpResult a)
- data CmpPredicate
- class Logic a where
- and :: a -> a -> CodeGenFunction r a
- or :: a -> a -> CodeGenFunction r a
- xor :: a -> a -> CodeGenFunction r a
- inv :: a -> CodeGenFunction r 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))
- decreaseArrayElementPtr :: 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 (T a) | |
Additive a => Additive (T a) | |
(Additive a, Additive b) => Additive (a, b) | |
(Positive n, Additive a) => Additive (T n a) | |
(Flags flags, Tuple a, Additive a) => Additive (Context flags a) | |
(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) | |
PseudoRing a => PseudoRing (T a) | |
PseudoRing a => PseudoRing (T a) | |
(Positive n, PseudoRing a) => PseudoRing (T n a) | |
(Flags flags, PseudoRing a, Tuple a) => PseudoRing (Context flags a) |
square :: PseudoRing a => a -> CodeGenFunction r aSource
class (PseudoRing (Scalar v), Additive v) => PseudoModule v whereSource
Methods
scale :: Scalar v -> v -> CodeGenFunction r vSource
Instances
PseudoModule v => PseudoModule (Value v) | |
PseudoModule v => PseudoModule (ConstValue v) | |
PseudoRing a => PseudoModule (T a) | |
PseudoModule a => PseudoModule (T a) | |
(Positive n, PseudoModule a) => PseudoModule (T n a) | |
(Flags flags, PseudoModule v, Tuple v, ~ * (Scalar v) a, Tuple a) => PseudoModule (Context flags v) |
class PseudoRing a => Field a whereSource
Methods
fdiv :: a -> a -> CodeGenFunction r aSource
class IntegerConstant a whereSource
Methods
fromInteger' :: Integer -> aSource
Instances
IntegerConstant a => IntegerConstant (Value a) | |
IntegerConstant a => IntegerConstant (ConstValue a) | |
IntegerConstant a => IntegerConstant (T a) | |
IntegerConstant a => IntegerConstant (T a) | |
(Positive n, IntegerConstant a) => IntegerConstant (T n a) | |
(Flags flags, Tuple a, IntegerConstant a) => IntegerConstant (Context flags a) |
class IntegerConstant a => RationalConstant a whereSource
Methods
fromRational' :: Rational -> aSource
Instances
RationalConstant a => RationalConstant (Value a) | |
RationalConstant a => RationalConstant (ConstValue a) | |
RationalConstant a => RationalConstant (T a) | |
RationalConstant a => RationalConstant (T a) | |
(Positive n, RationalConstant a) => RationalConstant (T n a) | |
(Flags flags, Tuple a, RationalConstant a) => RationalConstant (Context flags a) |
idiv :: IsInteger a => Value a -> Value a -> CodeGenFunction r (Value a)Source
In Haskell terms this is a quot
.
class Comparison a => FloatingComparison a whereSource
Methods
fcmp :: FPPredicate -> a -> a -> CodeGenFunction r (CmpResult a)Source
Instances
(IsFloating a, CmpRet a) => FloatingComparison (Value a) | |
(IsFloating a, CmpRet a) => FloatingComparison (ConstValue a) | |
FloatingComparison a => FloatingComparison (T a) | |
(Positive n, FloatingComparison a) => FloatingComparison (T n a) | |
(Flags flags, Tuple a, FloatingComparison a) => FloatingComparison (Context flags a) |
class Comparison a whereSource
Methods
cmp :: CmpPredicate -> a -> a -> CodeGenFunction r (CmpResult a)Source
Instances
CmpRet a => Comparison (Value a) | |
CmpRet a => Comparison (ConstValue a) | |
Comparison a => Comparison (T a) | |
(Positive n, Comparison a) => Comparison (T n a) | |
(Flags flags, Tuple a, Comparison a) => Comparison (Context flags a) |
data CmpPredicate
Methods
and :: a -> a -> CodeGenFunction r aSource
or :: a -> a -> CodeGenFunction r aSource
xor :: a -> a -> CodeGenFunction r aSource
inv :: a -> CodeGenFunction r aSource
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
decreaseArrayElementPtr :: Value (Ptr a) -> CodeGenFunction r (Value (Ptr a))Source
transcendental functions
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) | |
Transcendental a => Transcendental (T a) | |
Transcendental a => Transcendental (T a) | |
(Positive n, Transcendental a) => Transcendental (T n a) | |
(Flags flags, Tuple a, Transcendental a) => Transcendental (Context flags a) |