llvm-extra-0.12.0.1: Utility functions for the llvm interface
Safe HaskellSafe-Inferred
LanguageHaskell98

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 where Source #

Instances

Instances details
Fraction Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Fraction Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

(Positive n, Real a, IsFloating a, IsConst a) => Fraction (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

truncate :: Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

fraction :: Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

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, ShapeOf a ~ ShapeOf i) => Value a -> CodeGenFunction r (Value i) Source #

floorToInt :: (IsFloating a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, ShapeOf a ~ ShapeOf i) => Value a -> CodeGenFunction r (Value i) Source #

ceilingToInt :: (IsFloating a, CmpRet a, IsInteger i, IntegerConstant i, CmpRet i, CmpResult a ~ CmpResult i, ShapeOf a ~ ShapeOf 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, ShapeOf a ~ ShapeOf 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, ShapeOf a ~ ShapeOf i) => Value a -> CodeGenFunction r (Value i, Value a) Source #

type family Scalar vector #

Instances

Instances details
type Scalar Int16 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Int32 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Int64 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Int8 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Word16 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Word32 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Word64 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Word8 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar FP128 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar FP128 = FP128
type Scalar Bool 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Double 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Float 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Int 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Int = Int
type Scalar Word 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar (IntN d) 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar (IntN d) = IntN d
type Scalar (WordN d) 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar (WordN d) = WordN d
type Scalar (Vector n a) 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar (Vector n a) = a

class Replicate vector where #

Methods

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

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

Instances

Instances details
Replicate Int16 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Int32 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Int64 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Int8 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Word16 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Word32 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Word64 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Word8 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate FP128 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

replicate :: Value (Scalar FP128) -> CodeGenFunction r (Value FP128) #

replicateConst :: ConstValue (Scalar FP128) -> ConstValue FP128 #

Replicate Bool 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Double 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Float 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Int 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate Word 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Replicate (IntN d) 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

replicate :: Value (Scalar (IntN d)) -> CodeGenFunction r (Value (IntN d)) #

replicateConst :: ConstValue (Scalar (IntN d)) -> ConstValue (IntN d) #

Replicate (WordN d) 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

replicate :: Value (Scalar (WordN d)) -> CodeGenFunction r (Value (WordN d)) #

replicateConst :: ConstValue (Scalar (WordN d)) -> ConstValue (WordN d) #

(Positive n, IsPrimitive a) => Replicate (Vector n a) 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

replicate :: Value (Scalar (Vector n a)) -> CodeGenFunction r (Value (Vector n a)) #

replicateConst :: ConstValue (Scalar (Vector n a)) -> ConstValue (Vector n a) #

class IsArithmetic a => Real a where Source #

Instances

Instances details
Real Int16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Int32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Int64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Int8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Word16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Word32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Word64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Word8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real FP128 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

min :: Value FP128 -> Value FP128 -> CodeGenFunction r (Value FP128) Source #

max :: Value FP128 -> Value FP128 -> CodeGenFunction r (Value FP128) Source #

abs :: Value FP128 -> CodeGenFunction r (Value FP128) Source #

signum :: Value FP128 -> CodeGenFunction r (Value FP128) Source #

Real Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Int Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Real Word Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Positive n => Real (IntN n) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

min :: Value (IntN n) -> Value (IntN n) -> CodeGenFunction r (Value (IntN n)) Source #

max :: Value (IntN n) -> Value (IntN n) -> CodeGenFunction r (Value (IntN n)) Source #

abs :: Value (IntN n) -> CodeGenFunction r (Value (IntN n)) Source #

signum :: Value (IntN n) -> CodeGenFunction r (Value (IntN n)) Source #

Positive n => Real (WordN n) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

min :: Value (WordN n) -> Value (WordN n) -> CodeGenFunction r (Value (WordN n)) Source #

max :: Value (WordN n) -> Value (WordN n) -> CodeGenFunction r (Value (WordN n)) Source #

abs :: Value (WordN n) -> CodeGenFunction r (Value (WordN n)) Source #

signum :: Value (WordN n) -> CodeGenFunction r (Value (WordN n)) Source #

(Positive n, Real a) => Real (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

min :: Value (Vector n a) -> Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

max :: Value (Vector n a) -> Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

abs :: Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

signum :: Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

class IsInteger a => Saturated a where Source #

Instances

Instances details
Saturated Int16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Saturated Int32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Saturated Int64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Saturated Int8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Saturated Word16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Saturated Word32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Saturated Word64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Saturated Word8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Saturated Int Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Saturated Word Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Positive d => Saturated (IntN d) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value (IntN d) -> Value (IntN d) -> CodeGenFunction r (Value (IntN d)) Source #

subSat :: Value (IntN d) -> Value (IntN d) -> CodeGenFunction r (Value (IntN d)) Source #

Positive d => Saturated (WordN d) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value (WordN d) -> Value (WordN d) -> CodeGenFunction r (Value (WordN d)) Source #

subSat :: Value (WordN d) -> Value (WordN d) -> CodeGenFunction r (Value (WordN d)) Source #

(Positive n, IsPrimitive a, Saturated a, Bounded a, CmpRet a, IsConst a) => Saturated (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value (Vector n a) -> Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

subSat :: Value (Vector n a) -> Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

class (IsArithmetic (Scalar v), IsArithmetic v) => PseudoModule v where Source #

Methods

scale :: a ~ Scalar v => Value a -> Value v -> CodeGenFunction r (Value v) Source #

Instances

Instances details
PseudoModule Int16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Int32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Int64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Int8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Word16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Word32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Word64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Word8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Int Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

PseudoModule Word Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

(IsArithmetic a, IsPrimitive a, Positive n) => PseudoModule (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

scale :: a0 ~ Scalar (Vector n a) => Value a0 -> Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

class IsConst a => IntegerConstant a where Source #

Instances

Instances details
IntegerConstant Int16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Int32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Int64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Int8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Word16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Word32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Word64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Word8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Int Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

IntegerConstant Word Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Positive n => IntegerConstant (IntN n) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Positive n => IntegerConstant (WordN n) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue (WordN n) Source #

(IntegerConstant a, IsPrimitive a, Positive n) => IntegerConstant (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue (Vector n a) Source #

class IntegerConstant a => RationalConstant a where Source #

Instances

Instances details
RationalConstant Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

RationalConstant Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

(RationalConstant a, IsPrimitive a, Positive n) => RationalConstant (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromRational :: Rational -> ConstValue (Vector n a) Source #

class RationalConstant a => TranscendentalConstant a where Source #

Instances

Instances details
TranscendentalConstant Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

TranscendentalConstant Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

(TranscendentalConstant a, IsPrimitive a, Positive n) => TranscendentalConstant (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constPi :: ConstValue (Vector n a) Source #