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

LLVM.Extra.Arithmetic

Synopsis

arithmetic: generalized and improved type inference

class Zero a => Additive a where Source #

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.

Methods

zero :: a Source #

add :: a -> a -> CodeGenFunction r a Source #

sub :: a -> a -> CodeGenFunction r a Source #

neg :: a -> CodeGenFunction r a Source #

Instances

Instances details
Additive a => Additive (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

zero :: T a Source #

add :: T a -> T a -> CodeGenFunction r (T a) Source #

sub :: T a -> T a -> CodeGenFunction r (T a) Source #

neg :: T a -> CodeGenFunction r (T a) Source #

Additive a => Additive (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

Methods

zero :: T a Source #

add :: T a -> T a -> CodeGenFunction r (T a) Source #

sub :: T a -> T a -> CodeGenFunction r (T a) Source #

neg :: T a -> CodeGenFunction r (T a) Source #

IsInteger a => Additive (ConstValue a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

IsArithmetic a => Additive (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

(Flags flags, Tuple a, Additive a) => Additive (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

zero :: Context flags a Source #

add :: Context flags a -> Context flags a -> CodeGenFunction r (Context flags a) Source #

sub :: Context flags a -> Context flags a -> CodeGenFunction r (Context flags a) Source #

neg :: Context flags a -> CodeGenFunction r (Context flags a) Source #

(Positive n, Additive a) => Additive (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

zero :: T n a Source #

add :: T n a -> T n a -> CodeGenFunction r (T n a) Source #

sub :: T n a -> T n a -> CodeGenFunction r (T n a) Source #

neg :: T n a -> CodeGenFunction r (T n a) Source #

(Additive a, Additive b) => Additive (a, b) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

Methods

zero :: (a, b) Source #

add :: (a, b) -> (a, b) -> CodeGenFunction r (a, b) Source #

sub :: (a, b) -> (a, b) -> CodeGenFunction r (a, b) Source #

neg :: (a, b) -> CodeGenFunction r (a, b) Source #

(Additive a, Additive b, Additive c) => Additive (a, b, c) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

Methods

zero :: (a, b, c) Source #

add :: (a, b, c) -> (a, b, c) -> CodeGenFunction r (a, b, c) Source #

sub :: (a, b, c) -> (a, b, c) -> CodeGenFunction r (a, b, c) Source #

neg :: (a, b, c) -> CodeGenFunction r (a, b, c) Source #

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

Methods

mul :: a -> a -> CodeGenFunction r a Source #

Instances

Instances details
PseudoRing a => PseudoRing (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

mul :: T a -> T a -> CodeGenFunction r (T a) Source #

PseudoRing a => PseudoRing (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

Methods

mul :: T a -> T a -> CodeGenFunction r (T a) Source #

IsInteger v => PseudoRing (ConstValue v) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

IsArithmetic v => PseudoRing (Value v) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

Methods

mul :: Value v -> Value v -> CodeGenFunction r (Value v) Source #

(Flags flags, PseudoRing a, Tuple a) => PseudoRing (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

mul :: Context flags a -> Context flags a -> CodeGenFunction r (Context flags a) Source #

(Positive n, PseudoRing a) => PseudoRing (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

mul :: T n a -> T n a -> CodeGenFunction r (T n a) Source #

type family Scalar vector Source #

Instances

Instances details
type Scalar (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type Scalar (T a) = T (Scalar a)
type Scalar (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

type Scalar (T a) = T a
type Scalar (ConstValue a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

type Scalar (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

type Scalar (Value a) = Value (Scalar a)
type Scalar (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

type Scalar (Context flags a) = Context flags (Scalar a)
type Scalar (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

type Scalar (T n a) = T n (Scalar a)

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

Methods

scale :: Scalar v -> v -> CodeGenFunction r v Source #

Instances

Instances details
PseudoModule a => PseudoModule (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

scale :: Scalar (T a) -> T a -> CodeGenFunction r (T a) Source #

PseudoRing a => PseudoModule (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

Methods

scale :: Scalar (T a) -> T a -> CodeGenFunction r (T a) Source #

PseudoModule v => PseudoModule (Value v) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

Methods

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

(Flags flags, PseudoModule v, Tuple v, Scalar v ~ a, Tuple a) => PseudoModule (Context flags v) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

scale :: Scalar (Context flags v) -> Context flags v -> CodeGenFunction r (Context flags v) Source #

(Positive n, PseudoModule a) => PseudoModule (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

scale :: Scalar (T n a) -> T n a -> CodeGenFunction r (T n a) Source #

class PseudoRing a => Field a where Source #

Methods

fdiv :: a -> a -> CodeGenFunction r a Source #

Instances

Instances details
Field a => Field (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fdiv :: T a -> T a -> CodeGenFunction r (T a) Source #

Field a => Field (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

Methods

fdiv :: T a -> T a -> CodeGenFunction r (T a) Source #

IsFloating v => Field (Value v) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

Methods

fdiv :: Value v -> Value v -> CodeGenFunction r (Value v) Source #

(Flags flags, Tuple v, Field v) => Field (Context flags v) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fdiv :: Context flags v -> Context flags v -> CodeGenFunction r (Context flags v) Source #

(Positive n, Field a) => Field (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

fdiv :: T n a -> T n a -> CodeGenFunction r (T n a) Source #

class IntegerConstant a where Source #

Methods

fromInteger' :: Integer -> a Source #

Instances

Instances details
IntegerConstant a => IntegerConstant (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fromInteger' :: Integer -> T a Source #

IntegerConstant a => IntegerConstant (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

Methods

fromInteger' :: Integer -> T a Source #

IntegerConstant a => IntegerConstant (ConstValue a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

IntegerConstant a => IntegerConstant (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

(Flags flags, Tuple a, IntegerConstant a) => IntegerConstant (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fromInteger' :: Integer -> Context flags a Source #

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

Defined in LLVM.Extra.Multi.Vector

Methods

fromInteger' :: Integer -> T n a Source #

class IntegerConstant a => RationalConstant a where Source #

Instances

Instances details
RationalConstant a => RationalConstant (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

RationalConstant a => RationalConstant (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

RationalConstant a => RationalConstant (ConstValue a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

RationalConstant a => RationalConstant (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

(Flags flags, Tuple a, RationalConstant a) => RationalConstant (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fromRational' :: Rational -> Context flags a Source #

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

Defined in LLVM.Extra.Multi.Vector

Methods

fromRational' :: Rational -> T n a Source #

idiv :: IsInteger a => Value a -> Value a -> CodeGenFunction r (Value a) Source #

In Haskell terms this is a quot.

irem :: IsInteger a => Value a -> Value a -> CodeGenFunction r (Value a) Source #

class Comparison a => FloatingComparison a where Source #

Methods

fcmp :: FPPredicate -> a -> a -> CodeGenFunction r (CmpResult a) Source #

Instances

Instances details
FloatingComparison a => FloatingComparison (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

fcmp :: FPPredicate -> T a -> T a -> CodeGenFunction r (CmpResult (T a)) Source #

(IsFloating a, CmpRet a) => FloatingComparison (ConstValue a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

(IsFloating a, CmpRet a) => FloatingComparison (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

(Flags flags, Tuple a, FloatingComparison a) => FloatingComparison (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fcmp :: FPPredicate -> Context flags a -> Context flags a -> CodeGenFunction r (CmpResult (Context flags a)) Source #

(Positive n, FloatingComparison a) => FloatingComparison (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

fcmp :: FPPredicate -> T n a -> T n a -> CodeGenFunction r (CmpResult (T n a)) Source #

class Comparison a where Source #

Methods

cmp :: CmpPredicate -> a -> a -> CodeGenFunction r (CmpResult a) Source #

Instances

Instances details
Comparison a => Comparison (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Associated Types

type CmpResult (T a) Source #

Methods

cmp :: CmpPredicate -> T a -> T a -> CodeGenFunction r (CmpResult (T a)) Source #

CmpRet a => Comparison (ConstValue a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

Associated Types

type CmpResult (ConstValue a) Source #

CmpRet a => Comparison (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

Associated Types

type CmpResult (Value a) Source #

(Flags flags, Tuple a, Comparison a) => Comparison (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Associated Types

type CmpResult (Context flags a) Source #

Methods

cmp :: CmpPredicate -> Context flags a -> Context flags a -> CodeGenFunction r (CmpResult (Context flags a)) Source #

(Positive n, Comparison a) => Comparison (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type CmpResult (T n a) Source #

Methods

cmp :: CmpPredicate -> T n a -> T n a -> CodeGenFunction r (CmpResult (T n a)) Source #

type family CmpResult a Source #

Instances

Instances details
type CmpResult (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

type CmpResult (T a) = T Bool
type CmpResult (ConstValue a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

type CmpResult (ConstValue a) = ConstValue (CmpResult a)
type CmpResult (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

type CmpResult (Value a) = Value (CmpResult a)
type CmpResult (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

type CmpResult (Context flags a) = CmpResult a
type CmpResult (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

type CmpResult (T n a) = T n Bool

class Logic a where Source #

Methods

and :: a -> a -> CodeGenFunction r a Source #

or :: a -> a -> CodeGenFunction r a Source #

xor :: a -> a -> CodeGenFunction r a Source #

inv :: a -> CodeGenFunction r a Source #

Instances

Instances details
Logic a => Logic (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

and :: T a -> T a -> CodeGenFunction r (T a) Source #

or :: T a -> T a -> CodeGenFunction r (T a) Source #

xor :: T a -> T a -> CodeGenFunction r (T a) Source #

inv :: T a -> CodeGenFunction r (T a) Source #

IsInteger a => Logic (ConstValue a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

IsInteger a => Logic (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

(Positive n, Logic a) => Logic (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

and :: T n a -> T n a -> CodeGenFunction r (T n a) Source #

or :: T n a -> T n a -> CodeGenFunction r (T n a) Source #

xor :: T n a -> T n a -> CodeGenFunction r (T n a) Source #

inv :: T n a -> CodeGenFunction r (T n a) Source #

class Additive a => Real a where Source #

Methods

min :: a -> a -> CodeGenFunction r a Source #

max :: a -> a -> CodeGenFunction r a Source #

abs :: a -> CodeGenFunction r a Source #

signum :: a -> CodeGenFunction r a Source #

Instances

Instances details
Real a => Real (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

min :: T a -> T a -> CodeGenFunction r (T a) Source #

max :: T a -> T a -> CodeGenFunction r (T a) Source #

abs :: T a -> CodeGenFunction r (T a) Source #

signum :: T a -> CodeGenFunction r (T a) Source #

Real a => Real (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

Methods

min :: T a -> T a -> CodeGenFunction r (T a) Source #

max :: T a -> T a -> CodeGenFunction r (T a) Source #

abs :: T a -> CodeGenFunction r (T a) Source #

signum :: T a -> CodeGenFunction r (T a) Source #

Real a => Real (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

(Flags flags, Tuple a, Real a) => Real (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

min :: Context flags a -> Context flags a -> CodeGenFunction r (Context flags a) Source #

max :: Context flags a -> Context flags a -> CodeGenFunction r (Context flags a) Source #

abs :: Context flags a -> CodeGenFunction r (Context flags a) Source #

signum :: Context flags a -> CodeGenFunction r (Context flags a) Source #

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

Defined in LLVM.Extra.Multi.Vector

Methods

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

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

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

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

class Real a => Fraction a where Source #

Instances

Instances details
Fraction a => Fraction (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

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

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

Fraction a => Fraction (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

Methods

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

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

Fraction a => Fraction (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

(Flags flags, Tuple a, Fraction a) => Fraction (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

truncate :: Context flags a -> CodeGenFunction r (Context flags a) Source #

fraction :: Context flags a -> CodeGenFunction r (Context flags a) Source #

(Positive n, Fraction a) => Fraction (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

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

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

incPhase :: Fraction a => a -> a -> CodeGenFunction r a Source #

both increment and phase must be non-negative

pointer arithmetic

advanceArrayElementPtr :: IsType a => Value (Ptr a) -> CodeGenFunction r (Value (Ptr a)) #

decreaseArrayElementPtr :: IsType a => Value (Ptr a) -> CodeGenFunction r (Value (Ptr a)) #

transcendental functions

class Field a => Algebraic a where Source #

Methods

sqrt :: a -> CodeGenFunction r a Source #

Instances

Instances details
Algebraic a => Algebraic (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

sqrt :: T a -> CodeGenFunction r (T a) Source #

Algebraic a => Algebraic (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

Methods

sqrt :: T a -> CodeGenFunction r (T a) Source #

IsFloating a => Algebraic (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

Methods

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

(Flags flags, Tuple a, Algebraic a) => Algebraic (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

sqrt :: Context flags a -> CodeGenFunction r (Context flags a) Source #

(Positive n, Algebraic a) => Algebraic (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

sqrt :: T n a -> CodeGenFunction r (T n a) Source #

class Algebraic a => Transcendental a where Source #

Instances

Instances details
Transcendental a => Transcendental (T a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Private

Methods

pi :: CodeGenFunction r (T a) Source #

sin :: T a -> CodeGenFunction r (T a) Source #

cos :: T a -> CodeGenFunction r (T a) Source #

exp :: T a -> CodeGenFunction r (T a) Source #

log :: T a -> CodeGenFunction r (T a) Source #

pow :: T a -> T a -> CodeGenFunction r (T a) Source #

Transcendental a => Transcendental (T a) Source # 
Instance details

Defined in LLVM.Extra.Scalar

Methods

pi :: CodeGenFunction r (T a) Source #

sin :: T a -> CodeGenFunction r (T a) Source #

cos :: T a -> CodeGenFunction r (T a) Source #

exp :: T a -> CodeGenFunction r (T a) Source #

log :: T a -> CodeGenFunction r (T a) Source #

pow :: T a -> T a -> CodeGenFunction r (T a) Source #

(IsFloating a, TranscendentalConstant a) => Transcendental (Value a) Source # 
Instance details

Defined in LLVM.Extra.Arithmetic

(Flags flags, Tuple a, Transcendental a) => Transcendental (Context flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

pi :: CodeGenFunction r (Context flags a) Source #

sin :: Context flags a -> CodeGenFunction r (Context flags a) Source #

cos :: Context flags a -> CodeGenFunction r (Context flags a) Source #

exp :: Context flags a -> CodeGenFunction r (Context flags a) Source #

log :: Context flags a -> CodeGenFunction r (Context flags a) Source #

pow :: Context flags a -> Context flags a -> CodeGenFunction r (Context flags a) Source #

(Positive n, Transcendental a) => Transcendental (T n a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

pi :: CodeGenFunction r (T n a) Source #

sin :: T n a -> CodeGenFunction r (T n a) Source #

cos :: T n a -> CodeGenFunction r (T n a) Source #

exp :: T n a -> CodeGenFunction r (T n a) Source #

log :: T n a -> CodeGenFunction r (T n a) Source #

pow :: T n a -> T n a -> CodeGenFunction r (T n a) Source #

exp2 :: IsFloating a => Value a -> CodeGenFunction r (Value a) Source #

log2 :: IsFloating a => Value a -> CodeGenFunction r (Value a) Source #

log10 :: IsFloating a => Value a -> CodeGenFunction r (Value a) Source #