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

Safe HaskellNone

LLVM.Extra.ScalarOrVector

Description

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.

Synopsis

Documentation

class (Real a, IsFloating a) => Fraction a whereSource

Methods

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

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

Instances

Fraction Double 
Fraction Float 
(Positive n, Real a, IsFloating a, IsConst a) => Fraction (Vector n a) 

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

type family Scalar vector :: *Source

class Replicate vector whereSource

Methods

replicate :: Value (Scalar vector) -> CodeGenFunction r (Value vector)Source

an alternative is using the Constant vector type

replicateConst :: ConstValue (Scalar vector) -> ConstValue vectorSource

replicateOf :: (IsConst (Scalar v), Replicate v) => Scalar v -> Value vSource

class IsArithmetic a => Real a whereSource

Methods

min :: Value a -> Value a -> CodeGenFunction r (Value a)Source

max :: Value a -> Value a -> CodeGenFunction r (Value a)Source

abs :: Value a -> CodeGenFunction r (Value a)Source

signum :: Value a -> CodeGenFunction r (Value a)Source

Instances

Real Double 
Real Float 
Real Int8 
Real Int16 
Real Int32 
Real Int64 
Real Word8 
Real Word16 
Real Word32 
Real Word64 
Real FP128 
(Positive n, Real a) => Real (Vector n a) 

class (IsArithmetic (Scalar v), IsArithmetic v) => PseudoModule v whereSource

Methods

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

class IntegerConstant a => RationalConstant a whereSource

Methods

constFromRational :: Rational -> ConstValue aSource

Instances

RationalConstant Double 
RationalConstant Float 
(RationalConstant a, IsPrimitive a, Positive n) => RationalConstant (Vector n a) 

class RationalConstant a => TranscendentalConstant a whereSource

Methods

constPi :: ConstValue aSource