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

LLVM.Extra.Multi.Vector

Synopsis

Documentation

newtype T n a Source #

Constructors

Cons (Repr n a) 

Instances

Instances details
Positive n => C (T n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Class

Associated Types

type Size (T n) Source #

Methods

switch :: f T0 -> f (T (Size (T n))) -> f (T n) 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 #

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

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

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

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

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

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

Defined in LLVM.Extra.Multi.Vector

Methods

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

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

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

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

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

Defined in LLVM.Extra.Multi.Vector

Methods

fromRational' :: Rational -> T n 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 #

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

(IsType (Struct (Repr n a)), IsSized (Struct (Repr n a)), Positive n, C a, C (Repr n a)) => C (T n a) Source # 
Instance details

Defined in LLVM.Extra.Memory

Associated Types

type Struct (T n a) Source #

Methods

load :: Value (Ptr (Struct (T n a))) -> CodeGenFunction r (T n a) Source #

store :: T n a -> Value (Ptr (Struct (T n a))) -> CodeGenFunction r () Source #

decompose :: Value (Struct (T n a)) -> CodeGenFunction r (T n a) Source #

compose :: T n a -> CodeGenFunction r (Value (Struct (T n a))) Source #

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

Defined in LLVM.Extra.Multi.Vector

Methods

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

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

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

Defined in LLVM.Extra.Multi.Vector

Methods

undef :: T n a Source #

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

Defined in LLVM.Extra.Multi.Vector

Methods

zero :: T n a Source #

type Size (T n) Source # 
Instance details

Defined in LLVM.Extra.Multi.Class

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

Defined in LLVM.Extra.Multi.Vector

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

Defined in LLVM.Extra.Multi.Vector

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

Defined in LLVM.Extra.Memory

type Struct (T n a) = Struct (Repr n a)

consPrim :: Repr n a ~ Value n ar => Value n ar -> T n a Source #

deconsPrim :: Repr n a ~ Value n ar => T n a -> Value n ar Source #

class C a => C a where Source #

Associated Types

type Repr n a Source #

Methods

cons :: Positive n => Vector n a -> T n a Source #

undef :: Positive n => T n a Source #

zero :: Positive n => T n a Source #

phi :: Positive n => BasicBlock -> T n a -> CodeGenFunction r (T n a) Source #

addPhi :: Positive n => BasicBlock -> T n a -> T n a -> CodeGenFunction r () Source #

shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n a -> T n a -> CodeGenFunction r (T m a) Source #

extract :: Positive n => Value Word32 -> T n a -> CodeGenFunction r (T a) Source #

insert :: Positive n => Value Word32 -> T a -> T n a -> CodeGenFunction r (T n a) Source #

Instances

Instances details
C Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Int16 Source #

C Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Int32 Source #

C Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Int64 Source #

C Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Int8 Source #

C Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Word16 Source #

C Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Word32 Source #

C Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Word64 Source #

C Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Word8 Source #

C Bool8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Bool8 Source #

C Bool Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Bool Source #

C Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Double Source #

C Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Float Source #

C Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Int Source #

Methods

cons :: Positive n => Vector n Int -> T n Int Source #

undef :: Positive n => T n Int Source #

zero :: Positive n => T n Int Source #

phi :: Positive n => BasicBlock -> T n Int -> CodeGenFunction r (T n Int) Source #

addPhi :: Positive n => BasicBlock -> T n Int -> T n Int -> CodeGenFunction r () Source #

shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Int -> T n Int -> CodeGenFunction r (T m Int) Source #

extract :: Positive n => Value Word32 -> T n Int -> CodeGenFunction r (T Int) Source #

insert :: Positive n => Value Word32 -> T Int -> T n Int -> CodeGenFunction r (T n Int) Source #

C Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n Word Source #

C tuple => C (Tuple tuple) Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n (Tuple tuple) Source #

Methods

cons :: Positive n => Vector n (Tuple tuple) -> T n (Tuple tuple) Source #

undef :: Positive n => T n (Tuple tuple) Source #

zero :: Positive n => T n (Tuple tuple) Source #

phi :: Positive n => BasicBlock -> T n (Tuple tuple) -> CodeGenFunction r (T n (Tuple tuple)) Source #

addPhi :: Positive n => BasicBlock -> T n (Tuple tuple) -> T n (Tuple tuple) -> CodeGenFunction r () Source #

shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n (Tuple tuple) -> T n (Tuple tuple) -> CodeGenFunction r (T m (Tuple tuple)) Source #

extract :: Positive n => Value Word32 -> T n (Tuple tuple) -> CodeGenFunction r (T (Tuple tuple)) Source #

insert :: Positive n => Value Word32 -> T (Tuple tuple) -> T n (Tuple tuple) -> CodeGenFunction r (T n (Tuple tuple)) Source #

(Flags flags, MultiVector a) => C (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Associated Types

type Repr n (Number flags a) Source #

Methods

cons :: Positive n => Vector n (Number flags a) -> T n (Number flags a) Source #

undef :: Positive n => T n (Number flags a) Source #

zero :: Positive n => T n (Number flags a) Source #

phi :: Positive n => BasicBlock -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

addPhi :: Positive n => BasicBlock -> T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r () Source #

shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T m (Number flags a)) Source #

extract :: Positive n => Value Word32 -> T n (Number flags a) -> CodeGenFunction r (T (Number flags a)) Source #

insert :: Positive n => Value Word32 -> T (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

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

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n (a, b) Source #

Methods

cons :: Positive n => Vector n (a, b) -> T n (a, b) Source #

undef :: Positive n => T n (a, b) Source #

zero :: Positive n => T n (a, b) Source #

phi :: Positive n => BasicBlock -> T n (a, b) -> CodeGenFunction r (T n (a, b)) Source #

addPhi :: Positive n => BasicBlock -> T n (a, b) -> T n (a, b) -> CodeGenFunction r () Source #

shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n (a, b) -> T n (a, b) -> CodeGenFunction r (T m (a, b)) Source #

extract :: Positive n => Value Word32 -> T n (a, b) -> CodeGenFunction r (T (a, b)) Source #

insert :: Positive n => Value Word32 -> T (a, b) -> T n (a, b) -> CodeGenFunction r (T n (a, b)) Source #

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

Defined in LLVM.Extra.Multi.Vector

Associated Types

type Repr n (a, b, c) Source #

Methods

cons :: Positive n => Vector n (a, b, c) -> T n (a, b, c) Source #

undef :: Positive n => T n (a, b, c) Source #

zero :: Positive n => T n (a, b, c) Source #

phi :: Positive n => BasicBlock -> T n (a, b, c) -> CodeGenFunction r (T n (a, b, c)) Source #

addPhi :: Positive n => BasicBlock -> T n (a, b, c) -> T n (a, b, c) -> CodeGenFunction r () Source #

shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n (a, b, c) -> T n (a, b, c) -> CodeGenFunction r (T m (a, b, c)) Source #

extract :: Positive n => Value Word32 -> T n (a, b, c) -> CodeGenFunction r (T (a, b, c)) Source #

insert :: Positive n => Value Word32 -> T (a, b, c) -> T n (a, b, c) -> CodeGenFunction r (T n (a, b, c)) Source #

type Value n a = Value (Vector n a) Source #

map :: (Positive n, C a, C b) => (T a -> CodeGenFunction r (T b)) -> T n a -> CodeGenFunction r (T n b) Source #

zip :: T n a -> T n b -> T n (a, b) Source #

zip3 :: T n a -> T n b -> T n c -> T n (a, b, c) Source #

unzip :: T n (a, b) -> (T n a, T n b) Source #

unzip3 :: T n (a, b, c) -> (T n a, T n b, T n c) Source #

replicate :: (Positive n, C a) => T a -> CodeGenFunction r (T n a) Source #

iterate :: (Positive n, C a) => (T a -> CodeGenFunction r (T a)) -> T a -> CodeGenFunction r (T n a) Source #

take :: (Positive n, Positive m, C a) => T n a -> CodeGenFunction r (T m a) Source #

takeRev :: (Positive n, Positive m, C a) => T n a -> CodeGenFunction r (T m a) Source #

sum :: (Positive n, Additive a) => T n a -> CodeGenFunction r (T a) Source #

dotProduct :: (Positive n, PseudoRing a) => T n a -> T n a -> CodeGenFunction r (T a) Source #

cumulate :: (Positive n, Additive a) => T a -> T n a -> CodeGenFunction r (T a, T n a) Source #

cumulate1 :: (Positive n, Additive a) => T n a -> CodeGenFunction r (T n a) Source #

Needs (log n) vector additions

lift1 :: (Repr n a -> Repr n b) -> T n a -> T n b Source #

modify :: (Positive n, C a) => Value Word32 -> (T a -> CodeGenFunction r (T a)) -> T n a -> CodeGenFunction r (T n a) Source #

assemble :: (Positive n, C a) => [T a] -> CodeGenFunction r (T n a) Source #

dissect :: (Positive n, C a) => T n a -> CodeGenFunction r [T a] Source #

dissectList :: (Positive n, C a) => T n a -> [CodeGenFunction r (T a)] Source #

assemble1 :: (Positive n, C a) => T [] (T a) -> CodeGenFunction r (T n a) Source #

dissect1 :: (Positive n, C a) => T n a -> CodeGenFunction r (T [] (T a)) Source #

dissectList1 :: (Positive n, C a) => T n a -> T [] (CodeGenFunction r (T a)) Source #

assembleFromVector :: (Positive n, C a) => Vector n (T a) -> CodeGenFunction r (T n a) Source #

reverse :: (Positive n, C a) => T n a -> CodeGenFunction r (T n a) Source #

rotateUp :: (Positive n, C a) => T n a -> CodeGenFunction r (T n a) Source #

Rotate one element towards the higher elements.

I don't want to call it rotateLeft or rotateRight, because there is no prefered layout for the vector elements. In Intel's instruction manual vector elements are indexed like the bits, that is from right to left. However, when working with Haskell list and enumeration syntax, the start index is left.

rotateDown :: (Positive n, C a) => T n a -> CodeGenFunction r (T n a) Source #

shiftUp :: (Positive n, C a) => T a -> T n a -> CodeGenFunction r (T a, T n a) Source #

shiftDown :: (Positive n, C a) => T a -> T n a -> CodeGenFunction r (T a, T n a) Source #

shiftUpMultiZero :: (Positive n, C a) => Int -> T n a -> CodeGenFunction r (T n a) Source #

shiftDownMultiZero :: (Positive n, C a) => Int -> T n a -> CodeGenFunction r (T n a) Source #

shiftUpMultiUndef :: (Positive n, C a) => Int -> T n a -> CodeGenFunction r (T n a) Source #

shiftDownMultiUndef :: (Positive n, C a) => Int -> T n a -> CodeGenFunction r (T n a) Source #

undefPrimitive :: (Positive n, IsPrimitive al, Repr n a ~ Value n al) => T n a Source #

shufflePrimitive :: (Positive n, Positive m, IsPrimitive al, Repr a ~ Value al, Repr n a ~ Value n al, Repr m a ~ Value m al) => ConstValue (Vector m Word32) -> T n a -> T n a -> CodeGenFunction r (T m a) Source #

extractPrimitive :: (Positive n, IsPrimitive al, Repr a ~ Value al, Repr n a ~ Value n al) => Value Word32 -> T n a -> CodeGenFunction r (T a) Source #

insertPrimitive :: (Positive n, IsPrimitive al, Repr a ~ Value al, Repr n a ~ Value n al) => Value Word32 -> T a -> T n a -> CodeGenFunction r (T n a) Source #

shuffleMatchTraversable :: (Positive n, C a, Traversable f) => ConstValue (Vector n Word32) -> f (T n a) -> CodeGenFunction r (f (T n a)) Source #

insertTraversable :: (Positive n, C a, Traversable f, Applicative f) => Value Word32 -> f (T a) -> f (T n a) -> CodeGenFunction r (f (T n a)) Source #

extractTraversable :: (Positive n, C a, Traversable f) => Value Word32 -> f (T n a) -> CodeGenFunction r (f (T a)) Source #

class (IntegerConstant a, C a) => IntegerConstant a where Source #

Methods

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

Instances

Instances details
IntegerConstant Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

IntegerConstant Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

IntegerConstant Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

IntegerConstant Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

fromInteger' :: Positive n => Integer -> T n Int8 Source #

IntegerConstant Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

IntegerConstant Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

IntegerConstant Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

IntegerConstant Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

IntegerConstant Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

IntegerConstant Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

IntegerConstant Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

fromInteger' :: Positive n => Integer -> T n Int Source #

IntegerConstant Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

fromInteger' :: Positive n => Integer -> T n Word Source #

(Flags flags, MultiVector a, IntegerConstant a) => IntegerConstant (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fromInteger' :: Positive n => Integer -> T n (Number flags a) Source #

class (RationalConstant a, IntegerConstant a) => RationalConstant a where Source #

Methods

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

Instances

Instances details
RationalConstant Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

RationalConstant Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

(Flags flags, MultiVector a, RationalConstant a) => RationalConstant (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fromRational' :: Positive n => Rational -> T n (Number flags a) Source #

class (Additive a, C a) => Additive a where Source #

Methods

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

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

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

Instances

Instances details
Additive Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

add :: Positive n => T n Int16 -> T n Int16 -> CodeGenFunction r (T n Int16) Source #

sub :: Positive n => T n Int16 -> T n Int16 -> CodeGenFunction r (T n Int16) Source #

neg :: Positive n => T n Int16 -> CodeGenFunction r (T n Int16) Source #

Additive Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

add :: Positive n => T n Int32 -> T n Int32 -> CodeGenFunction r (T n Int32) Source #

sub :: Positive n => T n Int32 -> T n Int32 -> CodeGenFunction r (T n Int32) Source #

neg :: Positive n => T n Int32 -> CodeGenFunction r (T n Int32) Source #

Additive Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

add :: Positive n => T n Int64 -> T n Int64 -> CodeGenFunction r (T n Int64) Source #

sub :: Positive n => T n Int64 -> T n Int64 -> CodeGenFunction r (T n Int64) Source #

neg :: Positive n => T n Int64 -> CodeGenFunction r (T n Int64) Source #

Additive Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

add :: Positive n => T n Int8 -> T n Int8 -> CodeGenFunction r (T n Int8) Source #

sub :: Positive n => T n Int8 -> T n Int8 -> CodeGenFunction r (T n Int8) Source #

neg :: Positive n => T n Int8 -> CodeGenFunction r (T n Int8) Source #

Additive Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Additive Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Additive Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Additive Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

add :: Positive n => T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source #

sub :: Positive n => T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source #

neg :: Positive n => T n Word8 -> CodeGenFunction r (T n Word8) Source #

Additive Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Additive Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

add :: Positive n => T n Float -> T n Float -> CodeGenFunction r (T n Float) Source #

sub :: Positive n => T n Float -> T n Float -> CodeGenFunction r (T n Float) Source #

neg :: Positive n => T n Float -> CodeGenFunction r (T n Float) Source #

Additive Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

add :: Positive n => T n Int -> T n Int -> CodeGenFunction r (T n Int) Source #

sub :: Positive n => T n Int -> T n Int -> CodeGenFunction r (T n Int) Source #

neg :: Positive n => T n Int -> CodeGenFunction r (T n Int) Source #

Additive Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

add :: Positive n => T n Word -> T n Word -> CodeGenFunction r (T n Word) Source #

sub :: Positive n => T n Word -> T n Word -> CodeGenFunction r (T n Word) Source #

neg :: Positive n => T n Word -> CodeGenFunction r (T n Word) Source #

(Flags flags, MultiVector a, Additive a) => Additive (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

add :: Positive n => T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

sub :: Positive n => T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

neg :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

class (PseudoRing a, Additive a) => PseudoRing a where Source #

Methods

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

Instances

Instances details
PseudoRing Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

mul :: Positive n => T n Double -> T n Double -> CodeGenFunction r (T n Double) Source #

PseudoRing Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

mul :: Positive n => T n Float -> T n Float -> CodeGenFunction r (T n Float) Source #

(Flags flags, MultiVector a, PseudoRing a) => PseudoRing (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

mul :: Positive n => T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

class (Field a, PseudoRing a) => Field a where Source #

Methods

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

Instances

Instances details
Field Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

fdiv :: Positive n => T n Double -> T n Double -> CodeGenFunction r (T n Double) Source #

Field Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

fdiv :: Positive n => T n Float -> T n Float -> CodeGenFunction r (T n Float) Source #

(Flags flags, MultiVector a, Field a) => Field (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fdiv :: Positive n => T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

scale :: (Positive n, PseudoRing a) => T a -> T n a -> CodeGenFunction r (T n a) Source #

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

Methods

scaleMulti :: Positive n => T n (Scalar v) -> T n v -> CodeGenFunction r (T n v) Source #

Instances

Instances details
PseudoModule Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

PseudoModule Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

scaleMulti :: Positive n => T n (Scalar Float) -> T n Float -> CodeGenFunction r (T n Float) Source #

class (Real a, Additive a) => Real a where Source #

Methods

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

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

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

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

Instances

Instances details
Real Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Real Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Real Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Real Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

min :: Positive n => T n Int8 -> T n Int8 -> CodeGenFunction r (T n Int8) Source #

max :: Positive n => T n Int8 -> T n Int8 -> CodeGenFunction r (T n Int8) Source #

abs :: Positive n => T n Int8 -> CodeGenFunction r (T n Int8) Source #

signum :: Positive n => T n Int8 -> CodeGenFunction r (T n Int8) Source #

Real Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Real Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Real Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Real Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Real Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Real Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Real Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

min :: Positive n => T n Int -> T n Int -> CodeGenFunction r (T n Int) Source #

max :: Positive n => T n Int -> T n Int -> CodeGenFunction r (T n Int) Source #

abs :: Positive n => T n Int -> CodeGenFunction r (T n Int) Source #

signum :: Positive n => T n Int -> CodeGenFunction r (T n Int) Source #

Real Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

min :: Positive n => T n Word -> T n Word -> CodeGenFunction r (T n Word) Source #

max :: Positive n => T n Word -> T n Word -> CodeGenFunction r (T n Word) Source #

abs :: Positive n => T n Word -> CodeGenFunction r (T n Word) Source #

signum :: Positive n => T n Word -> CodeGenFunction r (T n Word) Source #

(Flags flags, MultiVector a, Real a) => Real (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

min :: Positive n => T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

max :: Positive n => T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

abs :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

signum :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

class (Fraction a, Real a) => Fraction a where Source #

Methods

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

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

Instances

Instances details
Fraction Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Fraction Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

(Flags flags, MultiVector a, Fraction a) => Fraction (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

truncate :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

fraction :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

class (Positive n, Repr n i ~ Value n ir, NativeInteger i ir, IsPrimitive ir, IsInteger ir) => NativeInteger n i ir Source #

Instances

Instances details
Positive n => NativeInteger n Int16 Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeInteger n Int32 Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeInteger n Int64 Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeInteger n Int8 Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeInteger n Word16 Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeInteger n Word32 Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeInteger n Word64 Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeInteger n Word8 Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeInteger n Int Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeInteger n Word Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

class (Positive n, Repr n a ~ Value n ar, NativeFloating a ar, IsPrimitive ar, IsFloating ar) => NativeFloating n a ar Source #

Instances

Instances details
Positive n => NativeFloating n Double Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Positive n => NativeFloating n Float Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

fromIntegral :: (NativeInteger n i ir, NativeFloating n a ar) => T n i -> CodeGenFunction r (T n a) Source #

class (Algebraic a, Field a) => Algebraic a where Source #

Methods

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

Instances

Instances details
Algebraic Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

sqrt :: Positive n => T n Double -> CodeGenFunction r (T n Double) Source #

Algebraic Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

sqrt :: Positive n => T n Float -> CodeGenFunction r (T n Float) Source #

(Flags flags, MultiVector a, Algebraic a) => Algebraic (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

sqrt :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

class (Transcendental a, Algebraic a) => Transcendental a where Source #

Methods

pi :: Positive n => CodeGenFunction r (T n a) Source #

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

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

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

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

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

Instances

Instances details
Transcendental Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Transcendental Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

(Flags flags, MultiVector a, Transcendental a) => Transcendental (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

pi :: Positive n => CodeGenFunction r (T n (Number flags a)) Source #

sin :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

cos :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

exp :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

log :: Positive n => T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

pow :: Positive n => T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

class (FloatingComparison a, Comparison a) => FloatingComparison a where Source #

Methods

fcmp :: Positive n => FPPredicate -> T n a -> T n a -> CodeGenFunction r (T n Bool) Source #

Instances

Instances details
FloatingComparison Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

fcmp :: Positive n => FPPredicate -> T n Float -> T n Float -> CodeGenFunction r (T n Bool) Source #

(Flags flags, MultiVector a, FloatingComparison a) => FloatingComparison (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

fcmp :: Positive n => FPPredicate -> T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n Bool) Source #

class (Select a, C a) => Select a where Source #

Methods

select :: Positive n => T n Bool -> T n a -> T n a -> CodeGenFunction r (T n a) Source #

Instances

Instances details
Select Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Int16 -> T n Int16 -> CodeGenFunction r (T n Int16) Source #

Select Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Int32 -> T n Int32 -> CodeGenFunction r (T n Int32) Source #

Select Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Int64 -> T n Int64 -> CodeGenFunction r (T n Int64) Source #

Select Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Int8 -> T n Int8 -> CodeGenFunction r (T n Int8) Source #

Select Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Word16 -> T n Word16 -> CodeGenFunction r (T n Word16) Source #

Select Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Word32 -> T n Word32 -> CodeGenFunction r (T n Word32) Source #

Select Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Word64 -> T n Word64 -> CodeGenFunction r (T n Word64) Source #

Select Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source #

Select Bool Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Bool -> T n Bool -> CodeGenFunction r (T n Bool) Source #

Select Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Double -> T n Double -> CodeGenFunction r (T n Double) Source #

Select Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Float -> T n Float -> CodeGenFunction r (T n Float) Source #

Select Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Int -> T n Int -> CodeGenFunction r (T n Int) Source #

Select Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n Word -> T n Word -> CodeGenFunction r (T n Word) Source #

(Flags flags, MultiVector a, Select a) => Select (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

select :: Positive n => T n Bool -> T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n (Number flags a)) Source #

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

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n (a, b) -> T n (a, b) -> CodeGenFunction r (T n (a, b)) Source #

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

Defined in LLVM.Extra.Multi.Vector

Methods

select :: Positive n => T n Bool -> T n (a, b, c) -> T n (a, b, c) -> CodeGenFunction r (T n (a, b, c)) Source #

class (Comparison a, Real a) => Comparison a where Source #

Methods

cmp :: Positive n => CmpPredicate -> T n a -> T n a -> CodeGenFunction r (T n Bool) Source #

Instances

Instances details
Comparison Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Int16 -> T n Int16 -> CodeGenFunction r (T n Bool) Source #

Comparison Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Int32 -> T n Int32 -> CodeGenFunction r (T n Bool) Source #

Comparison Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Int64 -> T n Int64 -> CodeGenFunction r (T n Bool) Source #

Comparison Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Int8 -> T n Int8 -> CodeGenFunction r (T n Bool) Source #

Comparison Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Word16 -> T n Word16 -> CodeGenFunction r (T n Bool) Source #

Comparison Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Word32 -> T n Word32 -> CodeGenFunction r (T n Bool) Source #

Comparison Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Word64 -> T n Word64 -> CodeGenFunction r (T n Bool) Source #

Comparison Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Word8 -> T n Word8 -> CodeGenFunction r (T n Bool) Source #

Comparison Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Double -> T n Double -> CodeGenFunction r (T n Bool) Source #

Comparison Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Float -> T n Float -> CodeGenFunction r (T n Bool) Source #

Comparison Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Int -> T n Int -> CodeGenFunction r (T n Bool) Source #

Comparison Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

cmp :: Positive n => CmpPredicate -> T n Word -> T n Word -> CodeGenFunction r (T n Bool) Source #

(Flags flags, MultiVector a, Comparison a) => Comparison (Number flags a) Source # 
Instance details

Defined in LLVM.Extra.FastMath

Methods

cmp :: Positive n => CmpPredicate -> T n (Number flags a) -> T n (Number flags a) -> CodeGenFunction r (T n Bool) Source #

class (Logic a, C a) => Logic a where Source #

Methods

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

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

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

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

Instances

Instances details
Logic Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Logic Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Logic Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Logic Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

and :: Positive n => T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source #

or :: Positive n => T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source #

xor :: Positive n => T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source #

inv :: Positive n => T n Word8 -> CodeGenFunction r (T n Word8) Source #

Logic Bool Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

and :: Positive n => T n Bool -> T n Bool -> CodeGenFunction r (T n Bool) Source #

or :: Positive n => T n Bool -> T n Bool -> CodeGenFunction r (T n Bool) Source #

xor :: Positive n => T n Bool -> T n Bool -> CodeGenFunction r (T n Bool) Source #

inv :: Positive n => T n Bool -> CodeGenFunction r (T n Bool) Source #

class (BitShift a, C a) => BitShift a where Source #

Methods

shl :: Positive n => T n a -> T n a -> CodeGenFunction r (T n a) Source #

shr :: Positive n => T n a -> T n a -> CodeGenFunction r (T n a) Source #

Instances

Instances details
BitShift Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Int16 -> T n Int16 -> CodeGenFunction r (T n Int16) Source #

shr :: Positive n => T n Int16 -> T n Int16 -> CodeGenFunction r (T n Int16) Source #

BitShift Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Int32 -> T n Int32 -> CodeGenFunction r (T n Int32) Source #

shr :: Positive n => T n Int32 -> T n Int32 -> CodeGenFunction r (T n Int32) Source #

BitShift Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Int64 -> T n Int64 -> CodeGenFunction r (T n Int64) Source #

shr :: Positive n => T n Int64 -> T n Int64 -> CodeGenFunction r (T n Int64) Source #

BitShift Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Int8 -> T n Int8 -> CodeGenFunction r (T n Int8) Source #

shr :: Positive n => T n Int8 -> T n Int8 -> CodeGenFunction r (T n Int8) Source #

BitShift Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Word16 -> T n Word16 -> CodeGenFunction r (T n Word16) Source #

shr :: Positive n => T n Word16 -> T n Word16 -> CodeGenFunction r (T n Word16) Source #

BitShift Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Word32 -> T n Word32 -> CodeGenFunction r (T n Word32) Source #

shr :: Positive n => T n Word32 -> T n Word32 -> CodeGenFunction r (T n Word32) Source #

BitShift Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Word64 -> T n Word64 -> CodeGenFunction r (T n Word64) Source #

shr :: Positive n => T n Word64 -> T n Word64 -> CodeGenFunction r (T n Word64) Source #

BitShift Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source #

shr :: Positive n => T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source #

BitShift Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Int -> T n Int -> CodeGenFunction r (T n Int) Source #

shr :: Positive n => T n Int -> T n Int -> CodeGenFunction r (T n Int) Source #

BitShift Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Vector

Methods

shl :: Positive n => T n Word -> T n Word -> CodeGenFunction r (T n Word) Source #

shr :: Positive n => T n Word -> T n Word -> CodeGenFunction r (T n Word) Source #