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

LLVM.Extra.Vector

Synopsis

Documentation

class (Positive (Size v), Phi v, Undefined v) => Simple v where Source #

Instances

Instances details
(Positive n, IsPrimitive a) => Simple (Value (Vector n a)) Source # 
Instance details

Defined in LLVM.Extra.Vector

Associated Types

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

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

Methods

shuffleMatch :: ConstValue (Vector (Size (Value (Vector n a))) Word32) -> Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

extract :: Value Word32 -> Value (Vector n a) -> CodeGenFunction r (Element (Value (Vector n a))) Source #

(Positive n, Phi a, Undefined a) => Simple (Constant n a) Source # 
Instance details

Defined in LLVM.Extra.Vector

Associated Types

type Element (Constant n a) Source #

type Size (Constant n a) Source #

(Simple v0, Simple v1, Size v0 ~ Size v1) => Simple (v0, v1) Source # 
Instance details

Defined in LLVM.Extra.Vector

Associated Types

type Element (v0, v1) Source #

type Size (v0, v1) Source #

Methods

shuffleMatch :: ConstValue (Vector (Size (v0, v1)) Word32) -> (v0, v1) -> CodeGenFunction r (v0, v1) Source #

extract :: Value Word32 -> (v0, v1) -> CodeGenFunction r (Element (v0, v1)) Source #

(Simple v0, Simple v1, Simple v2, Size v0 ~ Size v1, Size v1 ~ Size v2) => Simple (v0, v1, v2) Source # 
Instance details

Defined in LLVM.Extra.Vector

Associated Types

type Element (v0, v1, v2) Source #

type Size (v0, v1, v2) Source #

Methods

shuffleMatch :: ConstValue (Vector (Size (v0, v1, v2)) Word32) -> (v0, v1, v2) -> CodeGenFunction r (v0, v1, v2) Source #

extract :: Value Word32 -> (v0, v1, v2) -> CodeGenFunction r (Element (v0, v1, v2)) Source #

class Simple v => C v where Source #

Allow to work on records of vectors as if they are vectors of records. This is a reasonable approach for records of different element types since processor vectors can only be built from elements of the same type. But also, say, for chunked stereo signal this makes sense. In this case we would work on Stereo (Value a).

Formerly we used a two-way dependency Vector - (Element, Size). Now we have only the dependency Vector -> (Element, Size). This means that we need some more type annotations as in umul32to64/assemble, on the other hand we can allow multiple vector types with respect to the same element type. E.g. we can provide a vector type with pair elements where the pair elements are interleaved in the vector.

Methods

insert :: Value Word32 -> Element v -> v -> CodeGenFunction r v Source #

Instances

Instances details
(Positive n, IsPrimitive a) => C (Value (Vector n a)) Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

insert :: Value Word32 -> Element (Value (Vector n a)) -> Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

(C v0, C v1, Size v0 ~ Size v1) => C (v0, v1) Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

insert :: Value Word32 -> Element (v0, v1) -> (v0, v1) -> CodeGenFunction r (v0, v1) Source #

(C v0, C v1, C v2, Size v0 ~ Size v1, Size v1 ~ Size v2) => C (v0, v1, v2) Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

insert :: Value Word32 -> Element (v0, v1, v2) -> (v0, v1, v2) -> CodeGenFunction r (v0, v1, v2) Source #

type family Element v Source #

Instances

Instances details
type Element (Value (Vector n a)) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Element (Value (Vector n a)) = Value a
type Element (Constant n a) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Element (Constant n a) = a
type Element (v0, v1) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Element (v0, v1) = (Element v0, Element v1)
type Element (v0, v1, v2) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Element (v0, v1, v2) = (Element v0, Element v1, Element v2)

type family Size v Source #

Instances

Instances details
type Size (Value (Vector n a)) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Size (Value (Vector n a)) = n
type Size (Constant n a) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Size (Constant n a) = n
type Size (v0, v1) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Size (v0, v1) = Size v0
type Size (v0, v1, v2) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Size (v0, v1, v2) = Size v0

class (n ~ Size (Construct n a), a ~ Element (Construct n a), C (Construct n a)) => Canonical n a Source #

Instances

Instances details
(Positive n, IsPrimitive a) => Canonical n (Value a) Source # 
Instance details

Defined in LLVM.Extra.Vector

Associated Types

type Construct n (Value a) Source #

(Canonical n a0, Canonical n a1) => Canonical n (a0, a1) Source # 
Instance details

Defined in LLVM.Extra.Vector

Associated Types

type Construct n (a0, a1) Source #

(Canonical n a0, Canonical n a1, Canonical n a2) => Canonical n (a0, a1, a2) Source # 
Instance details

Defined in LLVM.Extra.Vector

Associated Types

type Construct n (a0, a1, a2) Source #

type family Construct n a Source #

Instances

Instances details
type Construct n (Value a) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Construct n (Value a) = Value (Vector n a)
type Construct n (a0, a1) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Construct n (a0, a1) = (Construct n a0, Construct n a1)
type Construct n (a0, a1, a2) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Construct n (a0, a1, a2) = (Construct n a0, Construct n a1, Construct n a2)

size :: Positive n => Value (Vector n a) -> Int Source #

replicate :: C v => Element v -> CodeGenFunction r v Source #

Manually assemble a vector of equal values. Better use ScalarOrVector.replicate.

assemble :: C v => [Element v] -> CodeGenFunction r v Source #

construct a vector out of single elements

You must assert that the length of the list matches the vector size.

This can be considered the inverse of extractAll.

shuffle :: (C v, C w, Element v ~ Element w) => v -> ConstValue (Vector (Size w) Word32) -> CodeGenFunction r w Source #

Manually implement vector shuffling using insertelement and extractelement. In contrast to LLVM's built-in instruction it supports distinct vector sizes, but it allows only one input vector (or a tuple of vectors, but we cannot shuffle between them). For more complex shuffling we recommend extractAll and assemble.

rotateUp :: Simple v => v -> CodeGenFunction r v 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.

shiftUp :: C v => Element v -> v -> CodeGenFunction r (Element v, v) Source #

shiftDown :: C v => Element v -> v -> CodeGenFunction r (Element v, v) Source #

shuffleMatchAccess :: C v => ConstValue (Vector (Size v) Word32) -> v -> CodeGenFunction r v Source #

Implement the shuffleMatch method using the methods of the C class.

shuffleMatchPlain1 :: (Positive n, IsPrimitive a) => Value (Vector n a) -> ConstValue (Vector n Word32) -> CodeGenFunction r (Value (Vector n a)) Source #

shuffleMatchPlain2 :: (Positive n, IsPrimitive a) => Value (Vector n a) -> Value (Vector n a) -> ConstValue (Vector n Word32) -> CodeGenFunction r (Value (Vector n a)) Source #

extractAll :: Simple v => v -> CodeGenFunction r [Element v] Source #

provide the elements of a vector as a list of individual virtual registers

This can be considered the inverse of assemble.

data Constant n a Source #

Instances

Instances details
Foldable (Constant n) Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

fold :: Monoid m => Constant n m -> m #

foldMap :: Monoid m => (a -> m) -> Constant n a -> m #

foldMap' :: Monoid m => (a -> m) -> Constant n a -> m #

foldr :: (a -> b -> b) -> b -> Constant n a -> b #

foldr' :: (a -> b -> b) -> b -> Constant n a -> b #

foldl :: (b -> a -> b) -> b -> Constant n a -> b #

foldl' :: (b -> a -> b) -> b -> Constant n a -> b #

foldr1 :: (a -> a -> a) -> Constant n a -> a #

foldl1 :: (a -> a -> a) -> Constant n a -> a #

toList :: Constant n a -> [a] #

null :: Constant n a -> Bool #

length :: Constant n a -> Int #

elem :: Eq a => a -> Constant n a -> Bool #

maximum :: Ord a => Constant n a -> a #

minimum :: Ord a => Constant n a -> a #

sum :: Num a => Constant n a -> a #

product :: Num a => Constant n a -> a #

Traversable (Constant n) Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

traverse :: Applicative f => (a -> f b) -> Constant n a -> f (Constant n b) #

sequenceA :: Applicative f => Constant n (f a) -> f (Constant n a) #

mapM :: Monad m => (a -> m b) -> Constant n a -> m (Constant n b) #

sequence :: Monad m => Constant n (m a) -> m (Constant n a) #

Applicative (Constant n) Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

pure :: a -> Constant n a #

(<*>) :: Constant n (a -> b) -> Constant n a -> Constant n b #

liftA2 :: (a -> b -> c) -> Constant n a -> Constant n b -> Constant n c #

(*>) :: Constant n a -> Constant n b -> Constant n b #

(<*) :: Constant n a -> Constant n b -> Constant n a #

Functor (Constant n) Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

fmap :: (a -> b) -> Constant n a -> Constant n b #

(<$) :: a -> Constant n b -> Constant n a #

Phi a => Phi (Constant n a) Source # 
Instance details

Defined in LLVM.Extra.Vector

Undefined a => Undefined (Constant n a) Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

undef :: Constant n a Source #

(Positive n, Phi a, Undefined a) => Simple (Constant n a) Source # 
Instance details

Defined in LLVM.Extra.Vector

Associated Types

type Element (Constant n a) Source #

type Size (Constant n a) Source #

type Element (Constant n a) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Element (Constant n a) = a
type Size (Constant n a) Source # 
Instance details

Defined in LLVM.Extra.Vector

type Size (Constant n a) = n

constant :: Positive n => a -> Constant n a Source #

insertChunk :: (C c, C v, Element c ~ Element v) => Int -> c -> v -> CodeGenFunction r v Source #

map :: (C v, C w, Size v ~ Size w) => (Element v -> CodeGenFunction r (Element w)) -> v -> CodeGenFunction r w Source #

Like LLVM.Util.Loop.mapVector but the loop is unrolled, which is faster since it can be packed by the code generator.

mapChunks :: (C ca, C cb, Size ca ~ Size cb, C va, C vb, Size va ~ Size vb, Element ca ~ Element va, Element cb ~ Element vb) => (ca -> CodeGenFunction r cb) -> va -> CodeGenFunction r vb Source #

zipChunksWith :: (C ca, C cb, C cc, Size ca ~ Size cb, Size cb ~ Size cc, C va, C vb, C vc, Size va ~ Size vb, Size vb ~ Size vc, Element ca ~ Element va, Element cb ~ Element vb, Element cc ~ Element vc) => (ca -> cb -> CodeGenFunction r cc) -> va -> vb -> CodeGenFunction r vc Source #

chop :: (C c, C v, Element c ~ Element v) => v -> [CodeGenFunction r c] Source #

If the target vector type is a native type then the chop operation produces no actual machine instruction. (nop) If the vector cannot be evenly divided into chunks the last chunk will be padded with undefined values.

concat :: (C c, C v, Element c ~ Element v) => [c] -> CodeGenFunction r v Source #

The target size is determined by the type. If the chunk list provides more data, the exceeding data is dropped. If the chunk list provides too few data, the target vector is filled with undefined elements.

signedFraction :: (IsFloating a, IsConst a, Real a, Positive n) => Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

cumulate1 :: (IsArithmetic a, IsPrimitive a, Positive n) => Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

Needs (log n) vector additions

class (IsArithmetic a, IsPrimitive a) => Arithmetic a where Source #

The order of addition is chosen for maximum efficiency. We do not try to prevent cancelations.

Minimal complete definition

Nothing

Methods

sum :: Positive n => Value (Vector n a) -> CodeGenFunction r (Value a) Source #

sumToPair :: Positive n => Value (Vector n a) -> CodeGenFunction r (Value a, Value a) Source #

The first result value is the sum of all vector elements from 0 to div n 2 + 1 and the second result value is the sum of vector elements from div n 2 to n-1. n must be at least D2.

sumInterleavedToPair :: Positive n => Value (Vector n a) -> CodeGenFunction r (Value a, Value a) Source #

Treat the vector as concatenation of pairs and all these pairs are added. Useful for stereo signal processing. n must be at least D2.

cumulate :: Positive n => Value a -> Value (Vector n a) -> CodeGenFunction r (Value a, Value (Vector n a)) Source #

dotProduct :: Positive n => Value (Vector n a) -> Value (Vector n a) -> CodeGenFunction r (Value a) Source #

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

Instances

Instances details
Arithmetic Int16 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

sum :: Positive n => Value (Vector n Int16) -> CodeGenFunction r (Value Int16) Source #

sumToPair :: Positive n => Value (Vector n Int16) -> CodeGenFunction r (Value Int16, Value Int16) Source #

sumInterleavedToPair :: Positive n => Value (Vector n Int16) -> CodeGenFunction r (Value Int16, Value Int16) Source #

cumulate :: Positive n => Value Int16 -> Value (Vector n Int16) -> CodeGenFunction r (Value Int16, Value (Vector n Int16)) Source #

dotProduct :: Positive n => Value (Vector n Int16) -> Value (Vector n Int16) -> CodeGenFunction r (Value Int16) Source #

mul :: Positive n => Value (Vector n Int16) -> Value (Vector n Int16) -> CodeGenFunction r (Value (Vector n Int16)) Source #

Arithmetic Int32 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

sum :: Positive n => Value (Vector n Int32) -> CodeGenFunction r (Value Int32) Source #

sumToPair :: Positive n => Value (Vector n Int32) -> CodeGenFunction r (Value Int32, Value Int32) Source #

sumInterleavedToPair :: Positive n => Value (Vector n Int32) -> CodeGenFunction r (Value Int32, Value Int32) Source #

cumulate :: Positive n => Value Int32 -> Value (Vector n Int32) -> CodeGenFunction r (Value Int32, Value (Vector n Int32)) Source #

dotProduct :: Positive n => Value (Vector n Int32) -> Value (Vector n Int32) -> CodeGenFunction r (Value Int32) Source #

mul :: Positive n => Value (Vector n Int32) -> Value (Vector n Int32) -> CodeGenFunction r (Value (Vector n Int32)) Source #

Arithmetic Int64 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

sum :: Positive n => Value (Vector n Int64) -> CodeGenFunction r (Value Int64) Source #

sumToPair :: Positive n => Value (Vector n Int64) -> CodeGenFunction r (Value Int64, Value Int64) Source #

sumInterleavedToPair :: Positive n => Value (Vector n Int64) -> CodeGenFunction r (Value Int64, Value Int64) Source #

cumulate :: Positive n => Value Int64 -> Value (Vector n Int64) -> CodeGenFunction r (Value Int64, Value (Vector n Int64)) Source #

dotProduct :: Positive n => Value (Vector n Int64) -> Value (Vector n Int64) -> CodeGenFunction r (Value Int64) Source #

mul :: Positive n => Value (Vector n Int64) -> Value (Vector n Int64) -> CodeGenFunction r (Value (Vector n Int64)) Source #

Arithmetic Int8 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

sum :: Positive n => Value (Vector n Int8) -> CodeGenFunction r (Value Int8) Source #

sumToPair :: Positive n => Value (Vector n Int8) -> CodeGenFunction r (Value Int8, Value Int8) Source #

sumInterleavedToPair :: Positive n => Value (Vector n Int8) -> CodeGenFunction r (Value Int8, Value Int8) Source #

cumulate :: Positive n => Value Int8 -> Value (Vector n Int8) -> CodeGenFunction r (Value Int8, Value (Vector n Int8)) Source #

dotProduct :: Positive n => Value (Vector n Int8) -> Value (Vector n Int8) -> CodeGenFunction r (Value Int8) Source #

mul :: Positive n => Value (Vector n Int8) -> Value (Vector n Int8) -> CodeGenFunction r (Value (Vector n Int8)) Source #

Arithmetic Word16 Source # 
Instance details

Defined in LLVM.Extra.Vector

Arithmetic Word32 Source # 
Instance details

Defined in LLVM.Extra.Vector

Arithmetic Word64 Source # 
Instance details

Defined in LLVM.Extra.Vector

Arithmetic Word8 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

sum :: Positive n => Value (Vector n Word8) -> CodeGenFunction r (Value Word8) Source #

sumToPair :: Positive n => Value (Vector n Word8) -> CodeGenFunction r (Value Word8, Value Word8) Source #

sumInterleavedToPair :: Positive n => Value (Vector n Word8) -> CodeGenFunction r (Value Word8, Value Word8) Source #

cumulate :: Positive n => Value Word8 -> Value (Vector n Word8) -> CodeGenFunction r (Value Word8, Value (Vector n Word8)) Source #

dotProduct :: Positive n => Value (Vector n Word8) -> Value (Vector n Word8) -> CodeGenFunction r (Value Word8) Source #

mul :: Positive n => Value (Vector n Word8) -> Value (Vector n Word8) -> CodeGenFunction r (Value (Vector n Word8)) Source #

Arithmetic Double Source # 
Instance details

Defined in LLVM.Extra.Vector

Arithmetic Float Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

sum :: Positive n => Value (Vector n Float) -> CodeGenFunction r (Value Float) Source #

sumToPair :: Positive n => Value (Vector n Float) -> CodeGenFunction r (Value Float, Value Float) Source #

sumInterleavedToPair :: Positive n => Value (Vector n Float) -> CodeGenFunction r (Value Float, Value Float) Source #

cumulate :: Positive n => Value Float -> Value (Vector n Float) -> CodeGenFunction r (Value Float, Value (Vector n Float)) Source #

dotProduct :: Positive n => Value (Vector n Float) -> Value (Vector n Float) -> CodeGenFunction r (Value Float) Source #

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

Arithmetic Int Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

sum :: Positive n => Value (Vector n Int) -> CodeGenFunction r (Value Int) Source #

sumToPair :: Positive n => Value (Vector n Int) -> CodeGenFunction r (Value Int, Value Int) Source #

sumInterleavedToPair :: Positive n => Value (Vector n Int) -> CodeGenFunction r (Value Int, Value Int) Source #

cumulate :: Positive n => Value Int -> Value (Vector n Int) -> CodeGenFunction r (Value Int, Value (Vector n Int)) Source #

dotProduct :: Positive n => Value (Vector n Int) -> Value (Vector n Int) -> CodeGenFunction r (Value Int) Source #

mul :: Positive n => Value (Vector n Int) -> Value (Vector n Int) -> CodeGenFunction r (Value (Vector n Int)) Source #

Arithmetic Word Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

sum :: Positive n => Value (Vector n Word) -> CodeGenFunction r (Value Word) Source #

sumToPair :: Positive n => Value (Vector n Word) -> CodeGenFunction r (Value Word, Value Word) Source #

sumInterleavedToPair :: Positive n => Value (Vector n Word) -> CodeGenFunction r (Value Word, Value Word) Source #

cumulate :: Positive n => Value Word -> Value (Vector n Word) -> CodeGenFunction r (Value Word, Value (Vector n Word)) Source #

dotProduct :: Positive n => Value (Vector n Word) -> Value (Vector n Word) -> CodeGenFunction r (Value Word) Source #

mul :: Positive n => Value (Vector n Word) -> Value (Vector n Word) -> CodeGenFunction r (Value (Vector n Word)) Source #

class (Arithmetic a, CmpRet a, IsPrimitive a, IsConst a) => Real a where Source #

Methods

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

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

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

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

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

floor :: Positive n => Value (Vector n a) -> CodeGenFunction r (Value (Vector n a)) Source #

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

Instances

Instances details
Real Int16 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

min :: Positive n => Value (Vector n Int16) -> Value (Vector n Int16) -> CodeGenFunction r (Value (Vector n Int16)) Source #

max :: Positive n => Value (Vector n Int16) -> Value (Vector n Int16) -> CodeGenFunction r (Value (Vector n Int16)) Source #

abs :: Positive n => Value (Vector n Int16) -> CodeGenFunction r (Value (Vector n Int16)) Source #

signum :: Positive n => Value (Vector n Int16) -> CodeGenFunction r (Value (Vector n Int16)) Source #

truncate :: Positive n => Value (Vector n Int16) -> CodeGenFunction r (Value (Vector n Int16)) Source #

floor :: Positive n => Value (Vector n Int16) -> CodeGenFunction r (Value (Vector n Int16)) Source #

fraction :: Positive n => Value (Vector n Int16) -> CodeGenFunction r (Value (Vector n Int16)) Source #

Real Int32 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

min :: Positive n => Value (Vector n Int32) -> Value (Vector n Int32) -> CodeGenFunction r (Value (Vector n Int32)) Source #

max :: Positive n => Value (Vector n Int32) -> Value (Vector n Int32) -> CodeGenFunction r (Value (Vector n Int32)) Source #

abs :: Positive n => Value (Vector n Int32) -> CodeGenFunction r (Value (Vector n Int32)) Source #

signum :: Positive n => Value (Vector n Int32) -> CodeGenFunction r (Value (Vector n Int32)) Source #

truncate :: Positive n => Value (Vector n Int32) -> CodeGenFunction r (Value (Vector n Int32)) Source #

floor :: Positive n => Value (Vector n Int32) -> CodeGenFunction r (Value (Vector n Int32)) Source #

fraction :: Positive n => Value (Vector n Int32) -> CodeGenFunction r (Value (Vector n Int32)) Source #

Real Int64 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

min :: Positive n => Value (Vector n Int64) -> Value (Vector n Int64) -> CodeGenFunction r (Value (Vector n Int64)) Source #

max :: Positive n => Value (Vector n Int64) -> Value (Vector n Int64) -> CodeGenFunction r (Value (Vector n Int64)) Source #

abs :: Positive n => Value (Vector n Int64) -> CodeGenFunction r (Value (Vector n Int64)) Source #

signum :: Positive n => Value (Vector n Int64) -> CodeGenFunction r (Value (Vector n Int64)) Source #

truncate :: Positive n => Value (Vector n Int64) -> CodeGenFunction r (Value (Vector n Int64)) Source #

floor :: Positive n => Value (Vector n Int64) -> CodeGenFunction r (Value (Vector n Int64)) Source #

fraction :: Positive n => Value (Vector n Int64) -> CodeGenFunction r (Value (Vector n Int64)) Source #

Real Int8 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

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

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

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

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

truncate :: Positive n => Value (Vector n Int8) -> CodeGenFunction r (Value (Vector n Int8)) Source #

floor :: Positive n => Value (Vector n Int8) -> CodeGenFunction r (Value (Vector n Int8)) Source #

fraction :: Positive n => Value (Vector n Int8) -> CodeGenFunction r (Value (Vector n Int8)) Source #

Real Word16 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

min :: Positive n => Value (Vector n Word16) -> Value (Vector n Word16) -> CodeGenFunction r (Value (Vector n Word16)) Source #

max :: Positive n => Value (Vector n Word16) -> Value (Vector n Word16) -> CodeGenFunction r (Value (Vector n Word16)) Source #

abs :: Positive n => Value (Vector n Word16) -> CodeGenFunction r (Value (Vector n Word16)) Source #

signum :: Positive n => Value (Vector n Word16) -> CodeGenFunction r (Value (Vector n Word16)) Source #

truncate :: Positive n => Value (Vector n Word16) -> CodeGenFunction r (Value (Vector n Word16)) Source #

floor :: Positive n => Value (Vector n Word16) -> CodeGenFunction r (Value (Vector n Word16)) Source #

fraction :: Positive n => Value (Vector n Word16) -> CodeGenFunction r (Value (Vector n Word16)) Source #

Real Word32 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

min :: Positive n => Value (Vector n Word32) -> Value (Vector n Word32) -> CodeGenFunction r (Value (Vector n Word32)) Source #

max :: Positive n => Value (Vector n Word32) -> Value (Vector n Word32) -> CodeGenFunction r (Value (Vector n Word32)) Source #

abs :: Positive n => Value (Vector n Word32) -> CodeGenFunction r (Value (Vector n Word32)) Source #

signum :: Positive n => Value (Vector n Word32) -> CodeGenFunction r (Value (Vector n Word32)) Source #

truncate :: Positive n => Value (Vector n Word32) -> CodeGenFunction r (Value (Vector n Word32)) Source #

floor :: Positive n => Value (Vector n Word32) -> CodeGenFunction r (Value (Vector n Word32)) Source #

fraction :: Positive n => Value (Vector n Word32) -> CodeGenFunction r (Value (Vector n Word32)) Source #

Real Word64 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

min :: Positive n => Value (Vector n Word64) -> Value (Vector n Word64) -> CodeGenFunction r (Value (Vector n Word64)) Source #

max :: Positive n => Value (Vector n Word64) -> Value (Vector n Word64) -> CodeGenFunction r (Value (Vector n Word64)) Source #

abs :: Positive n => Value (Vector n Word64) -> CodeGenFunction r (Value (Vector n Word64)) Source #

signum :: Positive n => Value (Vector n Word64) -> CodeGenFunction r (Value (Vector n Word64)) Source #

truncate :: Positive n => Value (Vector n Word64) -> CodeGenFunction r (Value (Vector n Word64)) Source #

floor :: Positive n => Value (Vector n Word64) -> CodeGenFunction r (Value (Vector n Word64)) Source #

fraction :: Positive n => Value (Vector n Word64) -> CodeGenFunction r (Value (Vector n Word64)) Source #

Real Word8 Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

min :: Positive n => Value (Vector n Word8) -> Value (Vector n Word8) -> CodeGenFunction r (Value (Vector n Word8)) Source #

max :: Positive n => Value (Vector n Word8) -> Value (Vector n Word8) -> CodeGenFunction r (Value (Vector n Word8)) Source #

abs :: Positive n => Value (Vector n Word8) -> CodeGenFunction r (Value (Vector n Word8)) Source #

signum :: Positive n => Value (Vector n Word8) -> CodeGenFunction r (Value (Vector n Word8)) Source #

truncate :: Positive n => Value (Vector n Word8) -> CodeGenFunction r (Value (Vector n Word8)) Source #

floor :: Positive n => Value (Vector n Word8) -> CodeGenFunction r (Value (Vector n Word8)) Source #

fraction :: Positive n => Value (Vector n Word8) -> CodeGenFunction r (Value (Vector n Word8)) Source #

Real Double Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

min :: Positive n => Value (Vector n Double) -> Value (Vector n Double) -> CodeGenFunction r (Value (Vector n Double)) Source #

max :: Positive n => Value (Vector n Double) -> Value (Vector n Double) -> CodeGenFunction r (Value (Vector n Double)) Source #

abs :: Positive n => Value (Vector n Double) -> CodeGenFunction r (Value (Vector n Double)) Source #

signum :: Positive n => Value (Vector n Double) -> CodeGenFunction r (Value (Vector n Double)) Source #

truncate :: Positive n => Value (Vector n Double) -> CodeGenFunction r (Value (Vector n Double)) Source #

floor :: Positive n => Value (Vector n Double) -> CodeGenFunction r (Value (Vector n Double)) Source #

fraction :: Positive n => Value (Vector n Double) -> CodeGenFunction r (Value (Vector n Double)) Source #

Real Float Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

min :: Positive n => Value (Vector n Float) -> Value (Vector n Float) -> CodeGenFunction r (Value (Vector n Float)) Source #

max :: Positive n => Value (Vector n Float) -> Value (Vector n Float) -> CodeGenFunction r (Value (Vector n Float)) Source #

abs :: Positive n => Value (Vector n Float) -> CodeGenFunction r (Value (Vector n Float)) Source #

signum :: Positive n => Value (Vector n Float) -> CodeGenFunction r (Value (Vector n Float)) Source #

truncate :: Positive n => Value (Vector n Float) -> CodeGenFunction r (Value (Vector n Float)) Source #

floor :: Positive n => Value (Vector n Float) -> CodeGenFunction r (Value (Vector n Float)) Source #

fraction :: Positive n => Value (Vector n Float) -> CodeGenFunction r (Value (Vector n Float)) Source #

Real Int Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

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

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

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

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

truncate :: Positive n => Value (Vector n Int) -> CodeGenFunction r (Value (Vector n Int)) Source #

floor :: Positive n => Value (Vector n Int) -> CodeGenFunction r (Value (Vector n Int)) Source #

fraction :: Positive n => Value (Vector n Int) -> CodeGenFunction r (Value (Vector n Int)) Source #

Real Word Source # 
Instance details

Defined in LLVM.Extra.Vector

Methods

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

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

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

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

truncate :: Positive n => Value (Vector n Word) -> CodeGenFunction r (Value (Vector n Word)) Source #

floor :: Positive n => Value (Vector n Word) -> CodeGenFunction r (Value (Vector n Word)) Source #

fraction :: Positive n => Value (Vector n Word) -> CodeGenFunction r (Value (Vector n Word)) Source #