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

Safe HaskellNone

LLVM.Extra.Storable

Contents

Description

Transfer values between Haskell and JIT generated code in a Haskell-compatible format as dictated by the Storable class. E.g. instance Bool may use more than a byte (e.g. Word32). For tuples, you may use the Tuple wrapper from the storable-record package. The Storable instance for Vectors is compatible with arrays, i.e. indices always count upwards irrespective of machine endianess and tuple elements are interleaved.

Synopsis

Basic class

class (Storable a, Value a, Phi (ValueOf a), Undefined (ValueOf a)) => C a whereSource

Instances

C Bool

Not very efficient implementation because we want to adapt to sizeOf Bool dynamically. Unfortunately, LLVM-9's optimizer does not recognize the instruction pattern. Better use Bool8 for booleans.

C Double 
C Float 
C Int 
C Int8 
C Int16 
C Int32 
C Int64 
C Word 
C Word8 
C Word16 
C Word32 
C Word64 
C () 
C Bool8 
C a => C (Complex a) 
Tuple tuple => C (Tuple tuple) 
(Positive n, Vector a, VectorValue n a, Phi (VectorValueOf n a)) => C (Vector n a) 

storeNext :: (C a, ValueOf a ~ al, Value (Ptr a) ~ ptr) => al -> ptr -> CodeGenFunction r ptrSource

modify :: (C a, ValueOf a ~ al) => (al -> CodeGenFunction r al) -> Value (Ptr a) -> CodeGenFunction r ()Source

Classes for tuples and vectors

class (Storable tuple, Value tuple, Phi (ValueOf tuple), Undefined (ValueOf tuple)) => Tuple tuple whereSource

Methods

loadTuple :: Value (Ptr (Tuple tuple)) -> CodeGenFunction r (ValueOf tuple)Source

storeTuple :: ValueOf tuple -> Value (Ptr (Tuple tuple)) -> CodeGenFunction r ()Source

Instances

(C a, C b) => Tuple (a, b) 
(C a, C b, C c) => Tuple (a, b, c) 

class TupleVector a whereSource

Methods

deinterleave :: Positive n => Proxy a -> Vector n (ValueOf a) -> CodeGenFunction r (VectorValueOf n a)Source

interleave :: Positive n => Proxy a -> VectorValueOf n a -> CodeGenFunction r (Vector n (ValueOf a))Source

Instances

(Vector a, Vector b) => TupleVector (a, b) 
(Vector a, Vector b, Vector c) => TupleVector (a, b, c) 

MultiValue support

Standard method implementations

loadNewtype :: (C a, ValueOf a ~ al) => (a -> wrapped) -> (al -> wrappedl) -> Value (Ptr wrapped) -> CodeGenFunction r wrappedlSource

storeNewtype :: (C a, ValueOf a ~ al) => (a -> wrapped) -> (wrappedl -> al) -> wrappedl -> Value (Ptr wrapped) -> CodeGenFunction r ()Source

loadTraversable :: (Repeat f, Traversable f, C a, ValueOf a ~ al) => Value (Ptr (f a)) -> CodeGenFunction r (f al)Source

loadApplicative :: (Applicative f, Traversable f, C a, ValueOf a ~ al) => Value (Ptr (f a)) -> CodeGenFunction r (f al)Source

storeFoldable :: (Foldable f, C a, ValueOf a ~ al) => f al -> Value (Ptr (f a)) -> CodeGenFunction r ()Source

Pointer handling

advancePtr :: (Storable a, Value (Ptr a) ~ ptr) => Value Int -> ptr -> CodeGenFunction r ptrSource

incrementPtr :: (Storable a, Value (Ptr a) ~ ptr) => ptr -> CodeGenFunction r ptrSource

decrementPtr :: (Storable a, Value (Ptr a) ~ ptr) => ptr -> CodeGenFunction r ptrSource

Loops over Storable arrays

arrayLoop :: (Phi s, Num i, IsConst i, IsInteger i, CmpRet i, IsPrimitive i, C a, Value (Ptr a) ~ ptrA) => Value i -> ptrA -> s -> (ptrA -> s -> CodeGenFunction r s) -> CodeGenFunction r sSource

arrayLoop2 :: (Phi s, Num i, IsConst i, IsInteger i, CmpRet i, IsPrimitive i, C a, Value (Ptr a) ~ ptrA, C b, Value (Ptr b) ~ ptrB) => Value i -> ptrA -> ptrB -> s -> (ptrA -> ptrB -> s -> CodeGenFunction r s) -> CodeGenFunction r sSource

arrayLoopMaybeCont :: (Phi s, Undefined s, Num i, IsConst i, IsInteger i, CmpRet i, IsPrimitive i, C a, Value (Ptr a) ~ ptrA, T (ptrA, s) ~ z) => Value i -> ptrA -> s -> (ptrA -> s -> T r z s) -> CodeGenFunction r (Value i, T s)Source

arrayLoopMaybeCont2 :: (Phi s, Undefined s, Num i, IsConst i, IsInteger i, CmpRet i, IsPrimitive i, C a, Value (Ptr a) ~ ptrA, C b, Value (Ptr b) ~ ptrB, T (ptrA, (ptrB, s)) ~ z) => Value i -> ptrA -> ptrB -> s -> (ptrA -> ptrB -> s -> T r z s) -> CodeGenFunction r (Value i, T s)Source