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

LLVM.Extra.Multi.Value.Storable

Synopsis

Basic class

class (Storable a, C a) => C a where Source #

Methods

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

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

Instances

Instances details
C Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Bool8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C () Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

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

store :: T () -> 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.Multi.Value.Storable

C Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

C Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

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

Defined in LLVM.Extra.Multi.Value.Storable

Methods

load :: Value (Ptr (Complex a)) -> CodeGenFunction r (T (Complex a)) Source #

store :: T (Complex a) -> Value (Ptr (Complex a)) -> CodeGenFunction r () Source #

(Marshal a, IsConst a, IsFirstClass a) => C (Stored a) Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

load :: Value (Ptr (Stored a)) -> CodeGenFunction r (T (Stored a)) Source #

store :: T (Stored a) -> Value (Ptr (Stored a)) -> CodeGenFunction r () Source #

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

Defined in LLVM.Extra.Multi.Value.Storable

Methods

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

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

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

Defined in LLVM.Extra.Multi.Value.Storable

Methods

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

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

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

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

Classes for tuples and vectors

class (Storable tuple, C tuple) => Tuple tuple where Source #

Methods

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

storeTuple :: T 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.Multi.Value.Storable

Methods

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

storeTuple :: T (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.Multi.Value.Storable

Methods

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

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

class (C a, C a) => Vector a where Source #

Methods

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

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

Instances

Instances details
Vector Int16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Int16 -> Vector n (Repr Int16) -> CodeGenFunction r (Repr n Int16) Source #

disassembleVector :: Positive n => Proxy Int16 -> Repr n Int16 -> CodeGenFunction r (Vector n (Repr Int16)) Source #

Vector Int32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Int32 -> Vector n (Repr Int32) -> CodeGenFunction r (Repr n Int32) Source #

disassembleVector :: Positive n => Proxy Int32 -> Repr n Int32 -> CodeGenFunction r (Vector n (Repr Int32)) Source #

Vector Int64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Int64 -> Vector n (Repr Int64) -> CodeGenFunction r (Repr n Int64) Source #

disassembleVector :: Positive n => Proxy Int64 -> Repr n Int64 -> CodeGenFunction r (Vector n (Repr Int64)) Source #

Vector Int8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Int8 -> Vector n (Repr Int8) -> CodeGenFunction r (Repr n Int8) Source #

disassembleVector :: Positive n => Proxy Int8 -> Repr n Int8 -> CodeGenFunction r (Vector n (Repr Int8)) Source #

Vector Word16 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Word16 -> Vector n (Repr Word16) -> CodeGenFunction r (Repr n Word16) Source #

disassembleVector :: Positive n => Proxy Word16 -> Repr n Word16 -> CodeGenFunction r (Vector n (Repr Word16)) Source #

Vector Word32 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Word32 -> Vector n (Repr Word32) -> CodeGenFunction r (Repr n Word32) Source #

disassembleVector :: Positive n => Proxy Word32 -> Repr n Word32 -> CodeGenFunction r (Vector n (Repr Word32)) Source #

Vector Word64 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Word64 -> Vector n (Repr Word64) -> CodeGenFunction r (Repr n Word64) Source #

disassembleVector :: Positive n => Proxy Word64 -> Repr n Word64 -> CodeGenFunction r (Vector n (Repr Word64)) Source #

Vector Word8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Word8 -> Vector n (Repr Word8) -> CodeGenFunction r (Repr n Word8) Source #

disassembleVector :: Positive n => Proxy Word8 -> Repr n Word8 -> CodeGenFunction r (Vector n (Repr Word8)) Source #

Vector Bool8 Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Bool8 -> Vector n (Repr Bool8) -> CodeGenFunction r (Repr n Bool8) Source #

disassembleVector :: Positive n => Proxy Bool8 -> Repr n Bool8 -> CodeGenFunction r (Vector n (Repr Bool8)) Source #

Vector Bool Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Bool -> Vector n (Repr Bool) -> CodeGenFunction r (Repr n Bool) Source #

disassembleVector :: Positive n => Proxy Bool -> Repr n Bool -> CodeGenFunction r (Vector n (Repr Bool)) Source #

Vector Double Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Double -> Vector n (Repr Double) -> CodeGenFunction r (Repr n Double) Source #

disassembleVector :: Positive n => Proxy Double -> Repr n Double -> CodeGenFunction r (Vector n (Repr Double)) Source #

Vector Float Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Float -> Vector n (Repr Float) -> CodeGenFunction r (Repr n Float) Source #

disassembleVector :: Positive n => Proxy Float -> Repr n Float -> CodeGenFunction r (Vector n (Repr Float)) Source #

Vector Int Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Int -> Vector n (Repr Int) -> CodeGenFunction r (Repr n Int) Source #

disassembleVector :: Positive n => Proxy Int -> Repr n Int -> CodeGenFunction r (Vector n (Repr Int)) Source #

Vector Word Source # 
Instance details

Defined in LLVM.Extra.Multi.Value.Storable

Methods

assembleVector :: Positive n => Proxy Word -> Vector n (Repr Word) -> CodeGenFunction r (Repr n Word) Source #

disassembleVector :: Positive n => Proxy Word -> Repr n Word -> CodeGenFunction r (Vector n (Repr Word)) Source #

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

Defined in LLVM.Extra.Multi.Value.Storable

Methods

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

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

class C a => TupleVector a where Source #

Methods

deinterleave :: Positive n => Proxy a -> Vector n (Repr a) -> CodeGenFunction r (Repr n a) Source #

interleave :: Positive n => Proxy a -> Repr n a -> CodeGenFunction r (Vector n (Repr a)) Source #

Instances

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

Defined in LLVM.Extra.Multi.Value.Storable

Methods

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

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

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

Defined in LLVM.Extra.Multi.Value.Storable

Methods

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

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

Standard method implementations

loadTraversable :: (Repeat f, Traversable f, C a, Repr fa ~ f (Repr a)) => Value (Ptr (f a)) -> CodeGenFunction r (T fa) Source #

loadApplicative :: (Applicative f, Traversable f, C a, Repr fa ~ f (Repr a)) => Value (Ptr (f a)) -> CodeGenFunction r (T fa) Source #

storeFoldable :: (Foldable f, C a, Repr fa ~ f (Repr a)) => T fa -> 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 #