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

Safe HaskellNone
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 #

Methods

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

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

Instances
Fraction Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

truncate :: Value Double -> CodeGenFunction r (Value Double) Source #

fraction :: Value Double -> CodeGenFunction r (Value Double) Source #

Fraction Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

truncate :: Value Float -> CodeGenFunction r (Value Float) Source #

fraction :: Value Float -> CodeGenFunction r (Value Float) Source #

(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 :: Type #

Instances
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 Int8 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

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 Word 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar Word8 
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 FP128 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

type Scalar FP128 = FP128
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
Replicate Bool 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Double 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Float 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Int 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Int8 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Int16 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Int32 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Int64 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Word 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Word8 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Word16 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Word32 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

Replicate Word64 
Instance details

Defined in LLVM.Extra.ScalarOrVectorPrivate

Methods

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

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

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 (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) #

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

class IsArithmetic a => Real a where Source #

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 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Int Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Int8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Int16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Int32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Int64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Word Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Word8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Word16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Word32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

Real Word64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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

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

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

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 #

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 #

Methods

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

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

Instances
Saturated Int Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Int -> Value Int -> CodeGenFunction r (Value Int) Source #

subSat :: Value Int -> Value Int -> CodeGenFunction r (Value Int) Source #

Saturated Int8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Int8 -> Value Int8 -> CodeGenFunction r (Value Int8) Source #

subSat :: Value Int8 -> Value Int8 -> CodeGenFunction r (Value Int8) Source #

Saturated Int16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Int16 -> Value Int16 -> CodeGenFunction r (Value Int16) Source #

subSat :: Value Int16 -> Value Int16 -> CodeGenFunction r (Value Int16) Source #

Saturated Int32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Int32 -> Value Int32 -> CodeGenFunction r (Value Int32) Source #

subSat :: Value Int32 -> Value Int32 -> CodeGenFunction r (Value Int32) Source #

Saturated Int64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Int64 -> Value Int64 -> CodeGenFunction r (Value Int64) Source #

subSat :: Value Int64 -> Value Int64 -> CodeGenFunction r (Value Int64) Source #

Saturated Word Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Word -> Value Word -> CodeGenFunction r (Value Word) Source #

subSat :: Value Word -> Value Word -> CodeGenFunction r (Value Word) Source #

Saturated Word8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Word8 -> Value Word8 -> CodeGenFunction r (Value Word8) Source #

subSat :: Value Word8 -> Value Word8 -> CodeGenFunction r (Value Word8) Source #

Saturated Word16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Word16 -> Value Word16 -> CodeGenFunction r (Value Word16) Source #

subSat :: Value Word16 -> Value Word16 -> CodeGenFunction r (Value Word16) Source #

Saturated Word32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Word32 -> Value Word32 -> CodeGenFunction r (Value Word32) Source #

subSat :: Value Word32 -> Value Word32 -> CodeGenFunction r (Value Word32) Source #

Saturated Word64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

addSat :: Value Word64 -> Value Word64 -> CodeGenFunction r (Value Word64) Source #

subSat :: Value Word64 -> Value Word64 -> CodeGenFunction r (Value Word64) Source #

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 #

scaleConst :: a ~ Scalar v => ConstValue a -> ConstValue v -> CodeGenFunction r (ConstValue v) Source #

Instances
PseudoModule Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Double => ConstValue a -> ConstValue Double -> CodeGenFunction r (ConstValue Double) Source #

PseudoModule Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Float => ConstValue a -> ConstValue Float -> CodeGenFunction r (ConstValue Float) Source #

PseudoModule Int Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Int => ConstValue a -> ConstValue Int -> CodeGenFunction r (ConstValue Int) Source #

PseudoModule Int8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Int8 => ConstValue a -> ConstValue Int8 -> CodeGenFunction r (ConstValue Int8) Source #

PseudoModule Int16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Int16 => ConstValue a -> ConstValue Int16 -> CodeGenFunction r (ConstValue Int16) Source #

PseudoModule Int32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Int32 => ConstValue a -> ConstValue Int32 -> CodeGenFunction r (ConstValue Int32) Source #

PseudoModule Int64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Int64 => ConstValue a -> ConstValue Int64 -> CodeGenFunction r (ConstValue Int64) Source #

PseudoModule Word Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Word => ConstValue a -> ConstValue Word -> CodeGenFunction r (ConstValue Word) Source #

PseudoModule Word8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Word8 => ConstValue a -> ConstValue Word8 -> CodeGenFunction r (ConstValue Word8) Source #

PseudoModule Word16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Word16 => ConstValue a -> ConstValue Word16 -> CodeGenFunction r (ConstValue Word16) Source #

PseudoModule Word32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Word32 => ConstValue a -> ConstValue Word32 -> CodeGenFunction r (ConstValue Word32) Source #

PseudoModule Word64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

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

scaleConst :: a ~ Scalar Word64 => ConstValue a -> ConstValue Word64 -> CodeGenFunction r (ConstValue Word64) Source #

(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 #

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

class IsConst a => IntegerConstant a where Source #

Methods

constFromInteger :: Integer -> ConstValue a Source #

Instances
IntegerConstant Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Double Source #

IntegerConstant Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Float Source #

IntegerConstant Int Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Int Source #

IntegerConstant Int8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Int8 Source #

IntegerConstant Int16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Int16 Source #

IntegerConstant Int32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Int32 Source #

IntegerConstant Int64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Int64 Source #

IntegerConstant Word Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Word Source #

IntegerConstant Word8 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Word8 Source #

IntegerConstant Word16 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Word16 Source #

IntegerConstant Word32 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Word32 Source #

IntegerConstant Word64 Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromInteger :: Integer -> ConstValue Word64 Source #

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

Defined in LLVM.Extra.ScalarOrVector

Methods

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

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 #

Methods

constFromRational :: Rational -> ConstValue a Source #

Instances
RationalConstant Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromRational :: Rational -> ConstValue Double Source #

RationalConstant Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constFromRational :: Rational -> ConstValue Float Source #

(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 #

Methods

constPi :: ConstValue a Source #

Instances
TranscendentalConstant Double Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constPi :: ConstValue Double Source #

TranscendentalConstant Float Source # 
Instance details

Defined in LLVM.Extra.ScalarOrVector

Methods

constPi :: ConstValue Float Source #

(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 #