Safe Haskell | None |
---|
Support for unified handling of scalars and vectors.
Attention:
The rounding and fraction functions only work
for floating point values with maximum magnitude of maxBound :: Int32
.
This way we save expensive handling of possibly seldom cases.
- class (Real a, IsFloating a) => Fraction a where
- signedFraction :: Fraction a => Value a -> CodeGenFunction r (Value a)
- addToPhase :: Fraction a => Value a -> Value a -> CodeGenFunction r (Value a)
- incPhase :: Fraction a => Value a -> Value a -> CodeGenFunction r (Value a)
- truncateToInt :: (IsFloating a, IsInteger i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i)
- floorToInt :: (IsFloating a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i)
- ceilingToInt :: (IsFloating a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i)
- roundToIntFast :: (IsFloating a, RationalConstant a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i)
- splitFractionToInt :: (IsFloating a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i, Value a)
- type family Scalar vector :: *
- class Replicate vector where
- replicate :: Value (Scalar vector) -> CodeGenFunction r (Value vector)
- replicateConst :: ConstValue (Scalar vector) -> ConstValue vector
- replicateOf :: (IsConst (Scalar v), Replicate v) => Scalar v -> Value v
- class IsArithmetic a => Real a where
- class (IsArithmetic (Scalar v), IsArithmetic v) => PseudoModule v where
- scale :: a ~ Scalar v => Value a -> Value v -> CodeGenFunction r (Value v)
- scaleConst :: a ~ Scalar v => ConstValue a -> ConstValue v -> CodeGenFunction r (ConstValue v)
- class IsConst a => IntegerConstant a where
- constFromInteger :: Integer -> ConstValue a
- class IntegerConstant a => RationalConstant a where
- constFromRational :: Rational -> ConstValue a
- class RationalConstant a => TranscendentalConstant a where
- constPi :: ConstValue a
Documentation
signedFraction :: Fraction a => Value a -> CodeGenFunction r (Value a)Source
The fraction has the same sign as the argument. This is not particular useful but fast on IEEE implementations.
addToPhase :: Fraction a => Value a -> Value a -> CodeGenFunction r (Value a)Source
increment (first operand) may be negative, phase must always be non-negative
incPhase :: Fraction a => Value a -> Value a -> CodeGenFunction r (Value a)Source
both increment and phase must be non-negative
truncateToInt :: (IsFloating a, IsInteger i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i)Source
floorToInt :: (IsFloating a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i)Source
ceilingToInt :: (IsFloating a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i)Source
roundToIntFast :: (IsFloating a, RationalConstant a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i)Source
Rounds to the next integer.
For numbers of the form n+0.5
,
we choose one of the neighboured integers
such that the overall implementation is most efficient.
splitFractionToInt :: (IsFloating a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, NumberOfElements a ~ NumberOfElements i) => Value a -> CodeGenFunction r (Value i, Value a)Source
replicateOf :: (IsConst (Scalar v), Replicate v) => Scalar v -> Value vSource
class (IsArithmetic (Scalar v), IsArithmetic v) => PseudoModule v whereSource
scale :: a ~ Scalar v => Value a -> Value v -> CodeGenFunction r (Value v)Source
scaleConst :: a ~ Scalar v => ConstValue a -> ConstValue v -> CodeGenFunction r (ConstValue v)Source
PseudoModule Double | |
PseudoModule Float | |
PseudoModule Int8 | |
PseudoModule Int16 | |
PseudoModule Int32 | |
PseudoModule Int64 | |
PseudoModule Word8 | |
PseudoModule Word16 | |
PseudoModule Word32 | |
PseudoModule Word64 | |
(IsArithmetic a, IsPrimitive a, Positive n) => PseudoModule (Vector n a) |
class IsConst a => IntegerConstant a whereSource
constFromInteger :: Integer -> ConstValue aSource
IntegerConstant Double | |
IntegerConstant Float | |
IntegerConstant Int8 | |
IntegerConstant Int16 | |
IntegerConstant Int32 | |
IntegerConstant Int64 | |
IntegerConstant Word8 | |
IntegerConstant Word16 | |
IntegerConstant Word32 | |
IntegerConstant Word64 | |
(IntegerConstant a, IsPrimitive a, Positive n) => IntegerConstant (Vector n a) |
class IntegerConstant a => RationalConstant a whereSource
constFromRational :: Rational -> ConstValue aSource
RationalConstant Double | |
RationalConstant Float | |
(RationalConstant a, IsPrimitive a, Positive n) => RationalConstant (Vector n a) |
class RationalConstant a => TranscendentalConstant a whereSource
TranscendentalConstant Double | |
TranscendentalConstant Float | |
(TranscendentalConstant a, IsPrimitive a, Positive n) => TranscendentalConstant (Vector n a) |