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

LLVM.Extra.Representation

Synopsis

Documentation

class (Phi llvmValue, IsType llvmStruct) => Memory llvmValue llvmStruct | llvmValue -> llvmStruct whereSource

An implementation of both MakeValueTuple and Memory must ensure that haskellValue is compatible with llvmStruct. That is, writing and reading llvmStruct by LLVM must be the same as accessing haskellValue by Storable methods.

We use a functional dependency in order to let type inference work nicely.

Methods

load :: Value (Ptr llvmStruct) -> CodeGenFunction r llvmValueSource

store :: llvmValue -> Value (Ptr llvmStruct) -> CodeGenFunction r (Value ())Source

decompose :: Value llvmStruct -> CodeGenFunction r llvmValueSource

compose :: llvmValue -> CodeGenFunction r (Value llvmStruct)Source

Instances

Memory () (Struct ()) 
IsFirstClass a => Memory (Value a) a 
(Memory al as, Memory bl bs, IsSized as sas, IsSized bs sbs) => Memory (al, bl) (Struct (as, (bs, ()))) 
(Memory al as, Memory bl bs, Memory cl cs, IsSized as sas, IsSized bs sbs, IsSized cs scs) => Memory (al, bl, cl) (Struct (as, (bs, (cs, ())))) 

modify :: Memory llvmValue llvmStruct => (llvmValue -> CodeGenFunction r llvmValue) -> Value (Ptr llvmStruct) -> CodeGenFunction r (Value ())Source

castStorablePtr :: (MakeValueTuple haskellValue llvmValue, Memory llvmValue llvmStruct) => Ptr haskellValue -> Ptr llvmStructSource

type MemoryRecord r o v = MemoryElement r o v vSource

data MemoryElement r o v x Source

Instances

memoryElement :: (Memory x llvmStruct, GetValue o n llvmStruct, GetElementPtr o (n, ()) llvmStruct) => (v -> x) -> n -> MemoryElement r o v xSource

loadRecord :: MemoryRecord r o llvmValue -> Value (Ptr o) -> CodeGenFunction r llvmValueSource

storeRecord :: MemoryRecord r o llvmValue -> llvmValue -> Value (Ptr o) -> CodeGenFunction r (Value ())Source

decomposeRecord :: MemoryRecord r o llvmValue -> Value o -> CodeGenFunction r llvmValueSource

composeRecord :: IsType o => MemoryRecord r o llvmValue -> llvmValue -> CodeGenFunction r (Value o)Source

loadNewtype :: Memory a o => (a -> llvmValue) -> Value (Ptr o) -> CodeGenFunction r llvmValueSource

storeNewtype :: Memory a o => (llvmValue -> a) -> llvmValue -> Value (Ptr o) -> CodeGenFunction r (Value ())Source

decomposeNewtype :: Memory a o => (a -> llvmValue) -> Value o -> CodeGenFunction r llvmValueSource

composeNewtype :: Memory a o => (llvmValue -> a) -> llvmValue -> CodeGenFunction r (Value o)Source

newForeignPtrParam :: (Storable b, MakeValueTuple b bl, Memory bl bp) => FunPtr (Ptr a -> IO ()) -> FunPtr (Ptr bp -> IO (Ptr a)) -> b -> IO (ForeignPtr a)Source

newForeignPtr :: Storable a => IO () -> a -> IO (ForeignPtr a)Source

Adding the finalizer to a ForeignPtr seems to be the only way that warrants execution of the finalizer (not too early and not never). However, the normal ForeignPtr finalizers must be independent from Haskell runtime. In contrast to ForeignPtr finalizers, addFinalizer adds finalizers to boxes, that are optimized away. Thus finalizers are run too early or not at all. Concurrent.ForeignPtr and using threaded execution is the only way to get finalizers in Haskell IO.

withForeignPtr :: (Storable a, MakeValueTuple a al, Memory al ap) => ForeignPtr a -> (Ptr ap -> IO b) -> IO bSource

malloc :: IsSized a s => CodeGenFunction r (Value (Ptr a))Source

Returns 16 Byte aligned piece of memory. Otherwise program crashes when vectors are part of the structure. I think that malloc in LLVM-2.5 and LLVM-2.6 is simply buggy.

FIXME: Aligning to 16 Byte might not be appropriate for all vector types on all platforms. Maybe we should use alignment of Storable class in order to determine the right alignment.