Safe Haskell | None |
---|
- 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
.
add :: a -> a -> CodeGenFunction r aSource
sub :: a -> a -> CodeGenFunction r aSource
neg :: a -> CodeGenFunction r aSource
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
mul :: a -> a -> CodeGenFunction r aSource
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) |
square :: PseudoRing a => a -> CodeGenFunction r aSource
class (PseudoRing (Scalar v), Additive v) => PseudoModule v whereSource
scale :: Scalar v -> v -> CodeGenFunction r vSource
PseudoModule v => PseudoModule (Value v) | |
PseudoModule v => PseudoModule (ConstValue v) | |
PseudoModule a => PseudoModule (T a) | |
PseudoRing a => PseudoModule (T a) | |
(Positive n, PseudoModule a) => PseudoModule (T n a) |
class PseudoRing a => Field a whereSource
fdiv :: a -> a -> CodeGenFunction r aSource
class IntegerConstant a whereSource
fromInteger' :: Integer -> aSource
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) |
class IntegerConstant a => RationalConstant a whereSource
fromRational' :: Rational -> aSource
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) |
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
fcmp :: FPPredicate -> a -> a -> CodeGenFunction r (CmpResult a)Source
(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) |
class Comparison a whereSource
cmp :: CmpPredicate -> a -> a -> CodeGenFunction r (CmpResult a)Source
CmpRet a => Comparison (Value a) | |
CmpRet a => Comparison (ConstValue a) | |
Comparison a => Comparison (T a) | |
(Positive n, Comparison a) => Comparison (T n a) |
data CmpPredicate
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
min :: a -> a -> CodeGenFunction r aSource
max :: a -> a -> CodeGenFunction r aSource
abs :: a -> CodeGenFunction r aSource
signum :: a -> CodeGenFunction r aSource
class Real a => Fraction a whereSource
truncate :: a -> CodeGenFunction r aSource
fraction :: 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
pi :: CodeGenFunction r aSource
sin, log, exp, cos :: a -> CodeGenFunction r aSource
pow :: a -> a -> CodeGenFunction r aSource
(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) |