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

LLVM.Extra.Storable

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 where Source #

Instances

Instances details
C Int16 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Int32 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Int64 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Int8 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Word16 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Word32 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Word64 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Word8 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Bool8 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C () Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Methods

load :: Value (Ptr ()) -> CodeGenFunction r (ValueOf ()) Source #

store :: ValueOf () -> Value (Ptr ()) -> CodeGenFunction r () Source #

C Bool Source #

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.

Instance details

Defined in LLVM.Extra.Storable.Private

C Double Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Float Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Int Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C Word Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

C a => C (Complex a) Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

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

Defined in LLVM.Extra.Storable.Private

Methods

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

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

(Positive n, Vector a, VectorValue n a, Phi (VectorValueOf n a)) => C (Vector n a) Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Methods

load :: Value (Ptr (Vector n a)) -> CodeGenFunction r (ValueOf (Vector n a)) Source #

store :: ValueOf (Vector n a) -> Value (Ptr (Vector n a)) -> CodeGenFunction r () Source #

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

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 where Source #

Methods

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

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

Instances

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

Defined in LLVM.Extra.Storable.Private

Methods

loadTuple :: Value (Ptr (Tuple (a, b))) -> CodeGenFunction r (ValueOf (a, b)) Source #

storeTuple :: ValueOf (a, b) -> Value (Ptr (Tuple (a, b))) -> CodeGenFunction r () Source #

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

Defined in LLVM.Extra.Storable.Private

Methods

loadTuple :: Value (Ptr (Tuple (a, b, c))) -> CodeGenFunction r (ValueOf (a, b, c)) Source #

storeTuple :: ValueOf (a, b, c) -> Value (Ptr (Tuple (a, b, c))) -> CodeGenFunction r () Source #

class C a => Vector a where Source #

Methods

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

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

Instances

Instances details
Vector Int16 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Int32 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Int64 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Int8 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Word16 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Word32 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Word64 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Word8 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Bool8 Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Bool Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Double Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Float Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Int Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Vector Word Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

(Tuple tuple, TupleVector tuple) => Vector (Tuple tuple) Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Methods

assembleVector :: Positive n => Proxy (Tuple tuple) -> Vector n (ValueOf (Tuple tuple)) -> CodeGenFunction r (VectorValueOf n (Tuple tuple)) Source #

disassembleVector :: Positive n => Proxy (Tuple tuple) -> VectorValueOf n (Tuple tuple) -> CodeGenFunction r (Vector n (ValueOf (Tuple tuple))) Source #

class TupleVector a where Source #

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

Instances details
(Vector a, Vector b) => TupleVector (a, b) Source # 
Instance details

Defined in LLVM.Extra.Storable.Private

Methods

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

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

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

Defined in LLVM.Extra.Storable.Private

Methods

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

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

Standard method implementations

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

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 ptr Source #

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

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

Loops over Storable arrays

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

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

arrayLoopMaybeCont :: (Phi s, Undefined s, Num i, IsConst i, IsInteger i, CmpRet i, IsPrimitive i, Storable 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, Storable a, Value (Ptr a) ~ ptrA, Storable 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 #