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

Safe HaskellNone

LLVM.Extra.Vector

Synopsis

Documentation

class (Positive (Size v), Phi v, Undefined v) => Simple v whereSource

Associated Types

type Element v :: *Source

type Size v :: *Source

Methods

shuffleMatch :: ConstValue (Vector (Size v) Word32) -> v -> CodeGenFunction r vSource

extract :: Value Word32 -> v -> CodeGenFunction r (Element v)Source

Instances

(Positive n, IsPrimitive a) => Simple (Value (Vector n a)) 
(Simple v0, Simple v1, ~ * (Size v0) (Size v1)) => Simple (v0, v1) 
(Positive n, Phi a, Undefined a) => Simple (Constant n a) 
(Simple v0, Simple v1, Simple v2, ~ * (Size v0) (Size v1), ~ * (Size v1) (Size v2)) => Simple (v0, v1, v2) 

class Simple v => C v whereSource

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 vSource

Instances

(Positive n, IsPrimitive a) => C (Value (Vector n a)) 
(C v0, C v1, ~ * (Size v0) (Size v1)) => C (v0, v1) 
(C v0, C v1, C v2, ~ * (Size v0) (Size v1), ~ * (Size v1) (Size v2)) => C (v0, v1, v2) 

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

Associated Types

type Construct n a :: *Source

Instances

(Positive n, IsPrimitive a) => Canonical n (Value a) 
(Canonical n a0, Canonical n a1) => Canonical n (a0, a1) 
(Canonical n a0, Canonical n a1, Canonical n a2) => Canonical n (a0, a1, a2) 

size :: Positive n => Value (Vector n a) -> IntSource

replicate :: C v => Element v -> CodeGenFunction r vSource

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

iterate :: C v => (Element v -> CodeGenFunction r (Element v)) -> Element v -> CodeGenFunction r vSource

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

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 wSource

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 vSource

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

reverse :: Simple v => v -> CodeGenFunction r vSource

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

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

shiftUpMultiZero :: (C v, Zero (Element v)) => Int -> v -> CodeGenFunction r vSource

shiftDownMultiZero :: (C v, Zero (Element v)) => Int -> v -> CodeGenFunction r vSource

shuffleMatchTraversable :: (Simple v, Traversable f) => ConstValue (Vector (Size v) Word32) -> f v -> CodeGenFunction r (f v)Source

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

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

insertTraversable :: (C v, Traversable f, Applicative f) => Value Word32 -> f (Element v) -> f v -> CodeGenFunction r (f v)Source

extractTraversable :: (Simple v, Traversable f) => Value Word32 -> f v -> CodeGenFunction r (f (Element v))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

Functor (Constant n) 
Applicative (Constant n) 
Foldable (Constant n) 
Traversable (Constant n) 
Phi a => Phi (Constant n a) 
Undefined a => Undefined (Constant n a) 
(Positive n, Phi a, Undefined a) => Simple (Constant n a) 

constant :: Positive n => a -> Constant n aSource

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

modify :: C v => Value Word32 -> (Element v -> CodeGenFunction r (Element v)) -> v -> CodeGenFunction r vSource

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

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 vbSource

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 vcSource

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 vSource

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.

select :: (IsFirstClass a, IsPrimitive a, Positive n, CmpRet a, CmpResult a ~ Bool) => Value (Vector n Bool) -> Value (Vector n a) -> Value (Vector n a) -> CodeGenFunction r (Value (Vector n a))Source

LLVM.select on boolean vectors cannot be translated to X86 code in LLVM-2.6, thus I code my own version that calls select on all elements. This is slow but works. When this issue is fixed, this function will be replaced by LLVM.select.

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

umul32to64 :: Positive n => Value (Vector n Word32) -> Value (Vector n Word32) -> CodeGenFunction r (Value (Vector n Word64))Source

class (IsArithmetic a, IsPrimitive a) => Arithmetic a whereSource

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

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

class (Arithmetic a, CmpRet a, CmpResult a ~ Bool, IsConst a) => Real a whereSource

Attention: The rounding and fraction functions only work for floating point values with maximum magnitude of maxBound :: Int32. This way we save expensive handling of possibly seldom cases.

Methods

min, 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, fraction, floor :: Positive n => Value (Vector n a) -> CodeGenFunction r (Value (Vector n a))Source