Safe Haskell | None |
---|---|
Language | Haskell98 |
LLVM.Extra.Multi.Vector
Synopsis
- newtype T n a = Cons (Repr n a)
- consPrim :: Repr n a ~ Value n ar => Value n ar -> T n a
- deconsPrim :: Repr n a ~ Value n ar => T n a -> Value n ar
- class C a => C a where
- type Repr n a
- cons :: Positive n => Vector n a -> T n a
- undef :: Positive n => T n a
- zero :: Positive n => T n a
- phi :: Positive n => BasicBlock -> T n a -> CodeGenFunction r (T n a)
- addPhi :: Positive n => BasicBlock -> T n a -> T n a -> CodeGenFunction r ()
- shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n a -> T n a -> CodeGenFunction r (T m a)
- extract :: Positive n => Value Word32 -> T n a -> CodeGenFunction r (T a)
- insert :: Positive n => Value Word32 -> T a -> T n a -> CodeGenFunction r (T n a)
- type Value n a = Value (Vector n a)
- map :: (Positive n, C a, C b) => (T a -> CodeGenFunction r (T b)) -> T n a -> CodeGenFunction r (T n b)
- zip :: T n a -> T n b -> T n (a, b)
- zip3 :: T n a -> T n b -> T n c -> T n (a, b, c)
- unzip :: T n (a, b) -> (T n a, T n b)
- unzip3 :: T n (a, b, c) -> (T n a, T n b, T n c)
- replicate :: (Positive n, C a) => T a -> CodeGenFunction r (T n a)
- iterate :: (Positive n, C a) => (T a -> CodeGenFunction r (T a)) -> T a -> CodeGenFunction r (T n a)
- take :: (Positive n, Positive m, C a) => T n a -> CodeGenFunction r (T m a)
- takeRev :: (Positive n, Positive m, C a) => T n a -> CodeGenFunction r (T m a)
- sum :: (Positive n, Additive a) => T n a -> CodeGenFunction r (T a)
- dotProduct :: (Positive n, PseudoRing a) => T n a -> T n a -> CodeGenFunction r (T a)
- cumulate :: (Positive n, Additive a) => T a -> T n a -> CodeGenFunction r (T a, T n a)
- cumulate1 :: (Positive n, Additive a) => T n a -> CodeGenFunction r (T n a)
- lift1 :: (Repr n a -> Repr n b) -> T n a -> T n b
- modify :: (Positive n, C a) => Value Word32 -> (T a -> CodeGenFunction r (T a)) -> T n a -> CodeGenFunction r (T n a)
- assemble :: (Positive n, C a) => [T a] -> CodeGenFunction r (T n a)
- dissect :: (Positive n, C a) => T n a -> CodeGenFunction r [T a]
- dissectList :: (Positive n, C a) => T n a -> [CodeGenFunction r (T a)]
- assemble1 :: (Positive n, C a) => T [] (T a) -> CodeGenFunction r (T n a)
- dissect1 :: (Positive n, C a) => T n a -> CodeGenFunction r (T [] (T a))
- dissectList1 :: (Positive n, C a) => T n a -> T [] (CodeGenFunction r (T a))
- assembleFromVector :: (Positive n, C a) => Vector n (T a) -> CodeGenFunction r (T n a)
- reverse :: (Positive n, C a) => T n a -> CodeGenFunction r (T n a)
- rotateUp :: (Positive n, C a) => T n a -> CodeGenFunction r (T n a)
- rotateDown :: (Positive n, C a) => T n a -> CodeGenFunction r (T n a)
- shiftUp :: (Positive n, C a) => T a -> T n a -> CodeGenFunction r (T a, T n a)
- shiftDown :: (Positive n, C a) => T a -> T n a -> CodeGenFunction r (T a, T n a)
- shiftUpMultiZero :: (Positive n, C a) => Int -> T n a -> CodeGenFunction r (T n a)
- shiftDownMultiZero :: (Positive n, C a) => Int -> T n a -> CodeGenFunction r (T n a)
- shiftUpMultiUndef :: (Positive n, C a) => Int -> T n a -> CodeGenFunction r (T n a)
- shiftDownMultiUndef :: (Positive n, C a) => Int -> T n a -> CodeGenFunction r (T n a)
- undefPrimitive :: (Positive n, IsPrimitive al, Repr n a ~ Value n al) => T n a
- 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)
- extractPrimitive :: (Positive n, IsPrimitive al, Repr a ~ Value al, Repr n a ~ Value n al) => Value Word32 -> T n a -> CodeGenFunction r (T a)
- 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)
- shuffleMatchTraversable :: (Positive n, C a, Traversable f) => ConstValue (Vector n Word32) -> f (T n a) -> CodeGenFunction r (f (T n a))
- insertTraversable :: (Positive n, C a, Traversable f, Applicative f) => Value Word32 -> f (T a) -> f (T n a) -> CodeGenFunction r (f (T n a))
- extractTraversable :: (Positive n, C a, Traversable f) => Value Word32 -> f (T n a) -> CodeGenFunction r (f (T a))
- class (IntegerConstant a, C a) => IntegerConstant a where
- fromInteger' :: Positive n => Integer -> T n a
- class (RationalConstant a, IntegerConstant a) => RationalConstant a where
- fromRational' :: Positive n => Rational -> T n a
- class (Additive a, C a) => Additive a where
- class (PseudoRing a, Additive a) => PseudoRing a where
- class (Field a, PseudoRing a) => Field a where
- scale :: (Positive n, PseudoRing a) => T a -> T n a -> CodeGenFunction r (T n a)
- class (PseudoModule v, PseudoRing (Scalar v), Additive v) => PseudoModule v where
- class (Real a, Additive a) => Real a where
- class (Fraction a, Real a) => Fraction a where
- class (Positive n, Repr n i ~ Value n ir, NativeInteger i ir, IsPrimitive ir, IsInteger ir) => NativeInteger n i ir
- class (Positive n, Repr n a ~ Value n ar, NativeFloating a ar, IsPrimitive ar, IsFloating ar) => NativeFloating n a ar
- fromIntegral :: (NativeInteger n i ir, NativeFloating n a ar) => T n i -> CodeGenFunction r (T n a)
- class (Algebraic a, Field a) => Algebraic a where
- class (Transcendental a, Algebraic a) => Transcendental a where
- class (FloatingComparison a, Comparison a) => FloatingComparison a where
- class (Select a, C a) => Select a where
- class (Comparison a, Real a) => Comparison a where
- class (Logic a, C a) => Logic a where
- class (BitShift a, C a) => BitShift a where
Documentation
Instances
class C a => C a where 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
C Bool Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Bool -> T n Bool Source # undef :: Positive n => T n Bool Source # zero :: Positive n => T n Bool Source # phi :: Positive n => BasicBlock -> T n Bool -> CodeGenFunction r (T n Bool) Source # addPhi :: Positive n => BasicBlock -> T n Bool -> T n Bool -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Bool -> T n Bool -> CodeGenFunction r (T m Bool) Source # extract :: Positive n => Value Word32 -> T n Bool -> CodeGenFunction r (T Bool) Source # insert :: Positive n => Value Word32 -> T Bool -> T n Bool -> CodeGenFunction r (T n Bool) Source # | |
C Double Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Double -> T n Double Source # undef :: Positive n => T n Double Source # zero :: Positive n => T n Double Source # phi :: Positive n => BasicBlock -> T n Double -> CodeGenFunction r (T n Double) Source # addPhi :: Positive n => BasicBlock -> T n Double -> T n Double -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Double -> T n Double -> CodeGenFunction r (T m Double) Source # extract :: Positive n => Value Word32 -> T n Double -> CodeGenFunction r (T Double) Source # insert :: Positive n => Value Word32 -> T Double -> T n Double -> CodeGenFunction r (T n Double) Source # | |
C Float Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Float -> T n Float Source # undef :: Positive n => T n Float Source # zero :: Positive n => T n Float Source # phi :: Positive n => BasicBlock -> T n Float -> CodeGenFunction r (T n Float) Source # addPhi :: Positive n => BasicBlock -> T n Float -> T n Float -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Float -> T n Float -> CodeGenFunction r (T m Float) Source # extract :: Positive n => Value Word32 -> T n Float -> CodeGenFunction r (T Float) Source # insert :: Positive n => Value Word32 -> T Float -> T n Float -> CodeGenFunction r (T n Float) Source # | |
C Int Source # | |
Defined in LLVM.Extra.Multi.Vector 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 Int8 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Int8 -> T n Int8 Source # undef :: Positive n => T n Int8 Source # zero :: Positive n => T n Int8 Source # phi :: Positive n => BasicBlock -> T n Int8 -> CodeGenFunction r (T n Int8) Source # addPhi :: Positive n => BasicBlock -> T n Int8 -> T n Int8 -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Int8 -> T n Int8 -> CodeGenFunction r (T m Int8) Source # extract :: Positive n => Value Word32 -> T n Int8 -> CodeGenFunction r (T Int8) Source # insert :: Positive n => Value Word32 -> T Int8 -> T n Int8 -> CodeGenFunction r (T n Int8) Source # | |
C Int16 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Int16 -> T n Int16 Source # undef :: Positive n => T n Int16 Source # zero :: Positive n => T n Int16 Source # phi :: Positive n => BasicBlock -> T n Int16 -> CodeGenFunction r (T n Int16) Source # addPhi :: Positive n => BasicBlock -> T n Int16 -> T n Int16 -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Int16 -> T n Int16 -> CodeGenFunction r (T m Int16) Source # extract :: Positive n => Value Word32 -> T n Int16 -> CodeGenFunction r (T Int16) Source # insert :: Positive n => Value Word32 -> T Int16 -> T n Int16 -> CodeGenFunction r (T n Int16) Source # | |
C Int32 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Int32 -> T n Int32 Source # undef :: Positive n => T n Int32 Source # zero :: Positive n => T n Int32 Source # phi :: Positive n => BasicBlock -> T n Int32 -> CodeGenFunction r (T n Int32) Source # addPhi :: Positive n => BasicBlock -> T n Int32 -> T n Int32 -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Int32 -> T n Int32 -> CodeGenFunction r (T m Int32) Source # extract :: Positive n => Value Word32 -> T n Int32 -> CodeGenFunction r (T Int32) Source # insert :: Positive n => Value Word32 -> T Int32 -> T n Int32 -> CodeGenFunction r (T n Int32) Source # | |
C Int64 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Int64 -> T n Int64 Source # undef :: Positive n => T n Int64 Source # zero :: Positive n => T n Int64 Source # phi :: Positive n => BasicBlock -> T n Int64 -> CodeGenFunction r (T n Int64) Source # addPhi :: Positive n => BasicBlock -> T n Int64 -> T n Int64 -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Int64 -> T n Int64 -> CodeGenFunction r (T m Int64) Source # extract :: Positive n => Value Word32 -> T n Int64 -> CodeGenFunction r (T Int64) Source # insert :: Positive n => Value Word32 -> T Int64 -> T n Int64 -> CodeGenFunction r (T n Int64) Source # | |
C Word Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Word -> T n Word Source # undef :: Positive n => T n Word Source # zero :: Positive n => T n Word Source # phi :: Positive n => BasicBlock -> T n Word -> CodeGenFunction r (T n Word) Source # addPhi :: Positive n => BasicBlock -> T n Word -> T n Word -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Word -> T n Word -> CodeGenFunction r (T m Word) Source # extract :: Positive n => Value Word32 -> T n Word -> CodeGenFunction r (T Word) Source # insert :: Positive n => Value Word32 -> T Word -> T n Word -> CodeGenFunction r (T n Word) Source # | |
C Word8 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Word8 -> T n Word8 Source # undef :: Positive n => T n Word8 Source # zero :: Positive n => T n Word8 Source # phi :: Positive n => BasicBlock -> T n Word8 -> CodeGenFunction r (T n Word8) Source # addPhi :: Positive n => BasicBlock -> T n Word8 -> T n Word8 -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Word8 -> T n Word8 -> CodeGenFunction r (T m Word8) Source # extract :: Positive n => Value Word32 -> T n Word8 -> CodeGenFunction r (T Word8) Source # insert :: Positive n => Value Word32 -> T Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source # | |
C Word16 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Word16 -> T n Word16 Source # undef :: Positive n => T n Word16 Source # zero :: Positive n => T n Word16 Source # phi :: Positive n => BasicBlock -> T n Word16 -> CodeGenFunction r (T n Word16) Source # addPhi :: Positive n => BasicBlock -> T n Word16 -> T n Word16 -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Word16 -> T n Word16 -> CodeGenFunction r (T m Word16) Source # extract :: Positive n => Value Word32 -> T n Word16 -> CodeGenFunction r (T Word16) Source # insert :: Positive n => Value Word32 -> T Word16 -> T n Word16 -> CodeGenFunction r (T n Word16) Source # | |
C Word32 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Word32 -> T n Word32 Source # undef :: Positive n => T n Word32 Source # zero :: Positive n => T n Word32 Source # phi :: Positive n => BasicBlock -> T n Word32 -> CodeGenFunction r (T n Word32) Source # addPhi :: Positive n => BasicBlock -> T n Word32 -> T n Word32 -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Word32 -> T n Word32 -> CodeGenFunction r (T m Word32) Source # extract :: Positive n => Value Word32 -> T n Word32 -> CodeGenFunction r (T Word32) Source # insert :: Positive n => Value Word32 -> T Word32 -> T n Word32 -> CodeGenFunction r (T n Word32) Source # | |
C Word64 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Word64 -> T n Word64 Source # undef :: Positive n => T n Word64 Source # zero :: Positive n => T n Word64 Source # phi :: Positive n => BasicBlock -> T n Word64 -> CodeGenFunction r (T n Word64) Source # addPhi :: Positive n => BasicBlock -> T n Word64 -> T n Word64 -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Word64 -> T n Word64 -> CodeGenFunction r (T m Word64) Source # extract :: Positive n => Value Word32 -> T n Word64 -> CodeGenFunction r (T Word64) Source # insert :: Positive n => Value Word32 -> T Word64 -> T n Word64 -> CodeGenFunction r (T n Word64) Source # | |
C Bool8 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods cons :: Positive n => Vector n Bool8 -> T n Bool8 Source # undef :: Positive n => T n Bool8 Source # zero :: Positive n => T n Bool8 Source # phi :: Positive n => BasicBlock -> T n Bool8 -> CodeGenFunction r (T n Bool8) Source # addPhi :: Positive n => BasicBlock -> T n Bool8 -> T n Bool8 -> CodeGenFunction r () Source # shuffle :: (Positive n, Positive m) => ConstValue (Vector m Word32) -> T n Bool8 -> T n Bool8 -> CodeGenFunction r (T m Bool8) Source # extract :: Positive n => Value Word32 -> T n Bool8 -> CodeGenFunction r (T Bool8) Source # insert :: Positive n => Value Word32 -> T Bool8 -> T n Bool8 -> CodeGenFunction r (T n Bool8) Source # | |
C tuple => C (Tuple tuple) Source # | |
Defined in LLVM.Extra.Multi.Vector 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 # | |
(C a, C b) => C (a, b) Source # | |
Defined in LLVM.Extra.Multi.Vector 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 # | |
(Flags flags, MultiVector a) => C (Number flags a) Source # | |
Defined in LLVM.Extra.FastMath 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 c) => C (a, b, c) Source # | |
Defined in LLVM.Extra.Multi.Vector 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 # |
map :: (Positive n, C a, C b) => (T a -> CodeGenFunction r (T b)) -> T n a -> CodeGenFunction r (T n b) Source #
iterate :: (Positive n, C a) => (T a -> CodeGenFunction r (T a)) -> T a -> CodeGenFunction r (T n a) Source #
dotProduct :: (Positive n, PseudoRing a) => T n a -> T n a -> CodeGenFunction r (T a) Source #
cumulate1 :: (Positive n, Additive a) => T n a -> CodeGenFunction r (T n a) Source #
Needs (log n) vector additions
modify :: (Positive n, C a) => Value Word32 -> (T a -> CodeGenFunction r (T 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.
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 #
Instances
IntegerConstant Double Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Float Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Int Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Int8 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Int16 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Int32 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Int64 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Word Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Word8 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Word16 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Word32 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
IntegerConstant Word64 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
(Flags flags, MultiVector a, IntegerConstant a) => IntegerConstant (Number flags a) Source # | |
Defined in LLVM.Extra.FastMath |
class (RationalConstant a, IntegerConstant a) => RationalConstant a where Source #
Instances
RationalConstant Double Source # | |
Defined in LLVM.Extra.Multi.Vector | |
RationalConstant Float Source # | |
Defined in LLVM.Extra.Multi.Vector | |
(Flags flags, MultiVector a, RationalConstant a) => RationalConstant (Number flags a) Source # | |
Defined in LLVM.Extra.FastMath |
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
Additive Double Source # | |
Additive Float Source # | |
Additive Int Source # | |
Additive Int8 Source # | |
Additive Int16 Source # | |
Additive Int32 Source # | |
Additive Int64 Source # | |
Additive Word Source # | |
Additive Word8 Source # | |
Additive Word16 Source # | |
Additive Word32 Source # | |
Additive Word64 Source # | |
(Flags flags, MultiVector a, Additive a) => Additive (Number flags a) Source # | |
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 #
Instances
PseudoRing Double Source # | |
PseudoRing Float Source # | |
(Flags flags, MultiVector a, PseudoRing a) => PseudoRing (Number flags a) Source # | |
class (Field a, PseudoRing a) => Field a where Source #
class (PseudoModule v, PseudoRing (Scalar v), Additive v) => PseudoModule v where Source #
Instances
PseudoModule Double Source # | |
PseudoModule 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
Real Double Source # | |
Defined in LLVM.Extra.Multi.Vector Methods min :: Positive n => T n Double -> T n Double -> CodeGenFunction r (T n Double) Source # max :: Positive n => T n Double -> T n Double -> CodeGenFunction r (T n Double) Source # abs :: Positive n => T n Double -> CodeGenFunction r (T n Double) Source # signum :: Positive n => T n Double -> CodeGenFunction r (T n Double) Source # | |
Real Float Source # | |
Defined in LLVM.Extra.Multi.Vector Methods min :: Positive n => T n Float -> T n Float -> CodeGenFunction r (T n Float) Source # max :: Positive n => T n Float -> T n Float -> CodeGenFunction r (T n Float) Source # abs :: Positive n => T n Float -> CodeGenFunction r (T n Float) Source # signum :: Positive n => T n Float -> CodeGenFunction r (T n Float) Source # | |
Real Int Source # | |
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 Int8 Source # | |
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 Int16 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods min :: Positive n => T n Int16 -> T n Int16 -> CodeGenFunction r (T n Int16) Source # max :: Positive n => T n Int16 -> T n Int16 -> CodeGenFunction r (T n Int16) Source # abs :: Positive n => T n Int16 -> CodeGenFunction r (T n Int16) Source # signum :: Positive n => T n Int16 -> CodeGenFunction r (T n Int16) Source # | |
Real Int32 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods min :: Positive n => T n Int32 -> T n Int32 -> CodeGenFunction r (T n Int32) Source # max :: Positive n => T n Int32 -> T n Int32 -> CodeGenFunction r (T n Int32) Source # abs :: Positive n => T n Int32 -> CodeGenFunction r (T n Int32) Source # signum :: Positive n => T n Int32 -> CodeGenFunction r (T n Int32) Source # | |
Real Int64 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods min :: Positive n => T n Int64 -> T n Int64 -> CodeGenFunction r (T n Int64) Source # max :: Positive n => T n Int64 -> T n Int64 -> CodeGenFunction r (T n Int64) Source # abs :: Positive n => T n Int64 -> CodeGenFunction r (T n Int64) Source # signum :: Positive n => T n Int64 -> CodeGenFunction r (T n Int64) Source # | |
Real Word Source # | |
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 # | |
Real Word8 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods min :: Positive n => T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source # max :: Positive n => T n Word8 -> T n Word8 -> CodeGenFunction r (T n Word8) Source # abs :: Positive n => T n Word8 -> CodeGenFunction r (T n Word8) Source # signum :: Positive n => T n Word8 -> CodeGenFunction r (T n Word8) Source # | |
Real Word16 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods min :: Positive n => T n Word16 -> T n Word16 -> CodeGenFunction r (T n Word16) Source # max :: Positive n => T n Word16 -> T n Word16 -> CodeGenFunction r (T n Word16) Source # abs :: Positive n => T n Word16 -> CodeGenFunction r (T n Word16) Source # signum :: Positive n => T n Word16 -> CodeGenFunction r (T n Word16) Source # | |
Real Word32 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods min :: Positive n => T n Word32 -> T n Word32 -> CodeGenFunction r (T n Word32) Source # max :: Positive n => T n Word32 -> T n Word32 -> CodeGenFunction r (T n Word32) Source # abs :: Positive n => T n Word32 -> CodeGenFunction r (T n Word32) Source # signum :: Positive n => T n Word32 -> CodeGenFunction r (T n Word32) Source # | |
Real Word64 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods min :: Positive n => T n Word64 -> T n Word64 -> CodeGenFunction r (T n Word64) Source # max :: Positive n => T n Word64 -> T n Word64 -> CodeGenFunction r (T n Word64) Source # abs :: Positive n => T n Word64 -> CodeGenFunction r (T n Word64) Source # signum :: Positive n => T n Word64 -> CodeGenFunction r (T n Word64) Source # | |
(Flags flags, MultiVector a, Real a) => Real (Number flags a) Source # | |
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 #
class (Positive n, Repr n i ~ Value n ir, NativeInteger i ir, IsPrimitive ir, IsInteger ir) => NativeInteger n i ir Source #
Instances
Positive n => NativeInteger n Int64 Int64 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeInteger n Int32 Int32 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeInteger n Int16 Int16 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeInteger n Int8 Int8 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeInteger n Int Int Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeInteger n Word64 Word64 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeInteger n Word32 Word32 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeInteger n Word16 Word16 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeInteger n Word8 Word8 Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeInteger n Word Word Source # | |
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
Positive n => NativeFloating n Double Double Source # | |
Defined in LLVM.Extra.Multi.Vector | |
Positive n => NativeFloating n Float Float Source # | |
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 (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
Transcendental Double Source # | |
Defined in LLVM.Extra.Multi.Vector Methods pi :: Positive n => CodeGenFunction r (T n Double) Source # sin :: Positive n => T n Double -> CodeGenFunction r (T n Double) Source # cos :: Positive n => T n Double -> CodeGenFunction r (T n Double) Source # exp :: Positive n => T n Double -> CodeGenFunction r (T n Double) Source # log :: Positive n => T n Double -> CodeGenFunction r (T n Double) Source # pow :: Positive n => T n Double -> T n Double -> CodeGenFunction r (T n Double) Source # | |
Transcendental Float Source # | |
Defined in LLVM.Extra.Multi.Vector Methods pi :: Positive n => CodeGenFunction r (T n Float) Source # sin :: Positive n => T n Float -> CodeGenFunction r (T n Float) Source # cos :: Positive n => T n Float -> CodeGenFunction r (T n Float) Source # exp :: Positive n => T n Float -> CodeGenFunction r (T n Float) Source # log :: Positive n => T n Float -> CodeGenFunction r (T n Float) Source # pow :: Positive n => T n Float -> T n Float -> CodeGenFunction r (T n Float) Source # | |
(Flags flags, MultiVector a, Transcendental a) => Transcendental (Number flags a) Source # | |
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 #
Instances
FloatingComparison Float Source # | |
(Flags flags, MultiVector a, FloatingComparison a) => FloatingComparison (Number flags a) Source # | |
class (Select a, C a) => Select a where Source #
Instances
Select Bool Source # | |
Select Double Source # | |
Select Float Source # | |
Select Int Source # | |
Select Int8 Source # | |
Select Int16 Source # | |
Select Int32 Source # | |
Select Int64 Source # | |
Select Word Source # | |
Select Word8 Source # | |
Select Word16 Source # | |
Select Word32 Source # | |
Select Word64 Source # | |
(Select a, Select b) => Select (a, b) Source # | |
(Flags flags, MultiVector a, Select a) => Select (Number flags a) Source # | |
(Select a, Select b, Select c) => Select (a, b, c) Source # | |
class (Comparison a, Real a) => Comparison a where Source #
Instances
Comparison Double Source # | |
Comparison Float Source # | |
Comparison Int Source # | |
Comparison Int8 Source # | |
Comparison Int16 Source # | |
Comparison Int32 Source # | |
Comparison Int64 Source # | |
Comparison Word Source # | |
Comparison Word8 Source # | |
Comparison Word16 Source # | |
Comparison Word32 Source # | |
Comparison Word64 Source # | |
(Flags flags, MultiVector a, Comparison a) => Comparison (Number flags a) 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
Logic Bool Source # | |
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 # | |
Logic Word8 Source # | |
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 Word16 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods and :: Positive n => T n Word16 -> T n Word16 -> CodeGenFunction r (T n Word16) Source # or :: Positive n => T n Word16 -> T n Word16 -> CodeGenFunction r (T n Word16) Source # xor :: Positive n => T n Word16 -> T n Word16 -> CodeGenFunction r (T n Word16) Source # inv :: Positive n => T n Word16 -> CodeGenFunction r (T n Word16) Source # | |
Logic Word32 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods and :: Positive n => T n Word32 -> T n Word32 -> CodeGenFunction r (T n Word32) Source # or :: Positive n => T n Word32 -> T n Word32 -> CodeGenFunction r (T n Word32) Source # xor :: Positive n => T n Word32 -> T n Word32 -> CodeGenFunction r (T n Word32) Source # inv :: Positive n => T n Word32 -> CodeGenFunction r (T n Word32) Source # | |
Logic Word64 Source # | |
Defined in LLVM.Extra.Multi.Vector Methods and :: Positive n => T n Word64 -> T n Word64 -> CodeGenFunction r (T n Word64) Source # or :: Positive n => T n Word64 -> T n Word64 -> CodeGenFunction r (T n Word64) Source # xor :: Positive n => T n Word64 -> T n Word64 -> CodeGenFunction r (T n Word64) Source # inv :: Positive n => T n Word64 -> CodeGenFunction r (T n Word64) 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 #