basement-0.0.6: Foundation scrap box of array & string

Safe HaskellNone
LanguageHaskell2010

Basement.PrimType

Synopsis

Documentation

class Eq ty => PrimType ty where Source #

Represent the accessor for types that can be stored in the UArray and MUArray.

Types need to be a instance of storable and have fixed sized.

Associated Types

type PrimSize ty :: Nat Source #

type level size of the given ty

Methods

primSizeInBytes :: Proxy ty -> CountOf Word8 Source #

get the size in bytes of a ty element

primShiftToBytes :: Proxy ty -> Int Source #

get the shift size

primBaUIndex :: ByteArray# -> Offset ty -> ty Source #

return the element stored at a specific index

primMbaURead Source #

Arguments

:: PrimMonad prim 
=> MutableByteArray# (PrimState prim)

mutable array to read from

-> Offset ty

index of the element to retrieve

-> prim ty

the element returned

Read an element at an index in a mutable array

primMbaUWrite Source #

Arguments

:: PrimMonad prim 
=> MutableByteArray# (PrimState prim)

mutable array to modify

-> Offset ty

index of the element to modify

-> ty

the new value to store

-> prim () 

Write an element to a specific cell in a mutable array.

primAddrIndex :: Addr# -> Offset ty -> ty Source #

Read from Address, without a state. the value read should be considered a constant for all pratical purpose, otherwise bad thing will happens.

primAddrRead :: PrimMonad prim => Addr# -> Offset ty -> prim ty Source #

Read a value from Addr in a specific primitive monad

primAddrWrite :: PrimMonad prim => Addr# -> Offset ty -> ty -> prim () Source #

Write a value to Addr in a specific primitive monad

Instances

PrimType Char Source # 
PrimType Double Source # 
PrimType Float Source # 
PrimType Int Source # 
PrimType Int8 Source # 
PrimType Int16 Source # 
PrimType Int32 Source # 
PrimType Int64 Source # 
PrimType Word Source # 
PrimType Word8 Source # 
PrimType Word16 Source # 
PrimType Word32 Source # 
PrimType Word64 Source # 
PrimType CChar Source # 
PrimType CUChar Source # 
PrimType Char7 Source # 
PrimType Word128 Source # 
PrimType Word256 Source # 
PrimType a => PrimType (BE a) Source # 

Associated Types

type PrimSize (BE a) :: Nat Source #

Methods

primSizeInBytes :: Proxy * (BE a) -> CountOf Word8 Source #

primShiftToBytes :: Proxy * (BE a) -> Int Source #

primBaUIndex :: ByteArray# -> Offset (BE a) -> BE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> prim (BE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (BE a) -> BE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (BE a) -> BE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (BE a) -> prim (BE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (BE a) -> BE a -> prim () Source #

PrimType a => PrimType (LE a) Source # 

Associated Types

type PrimSize (LE a) :: Nat Source #

Methods

primSizeInBytes :: Proxy * (LE a) -> CountOf Word8 Source #

primShiftToBytes :: Proxy * (LE a) -> Int Source #

primBaUIndex :: ByteArray# -> Offset (LE a) -> LE a Source #

primMbaURead :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> prim (LE a) Source #

primMbaUWrite :: PrimMonad prim => MutableByteArray# (PrimState prim) -> Offset (LE a) -> LE a -> prim () Source #

primAddrIndex :: Addr# -> Offset (LE a) -> LE a Source #

primAddrRead :: PrimMonad prim => Addr# -> Offset (LE a) -> prim (LE a) Source #

primAddrWrite :: PrimMonad prim => Addr# -> Offset (LE a) -> LE a -> prim () Source #

primMbaRead :: (PrimType ty, PrimMonad prim) => MutableByteArray# (PrimState prim) -> Offset ty -> prim ty Source #

primMbaWrite :: (PrimType ty, PrimMonad prim) => MutableByteArray# (PrimState prim) -> Offset ty -> ty -> prim () Source #

primArrayIndex :: Array# ty -> Offset ty -> ty Source #

primMutableArrayRead :: PrimMonad prim => MutableArray# (PrimState prim) ty -> Offset ty -> prim ty Source #

primMutableArrayWrite :: PrimMonad prim => MutableArray# (PrimState prim) ty -> Offset ty -> ty -> prim () Source #

primOffsetOfE :: forall a. PrimType a => Offset a -> Offset Word8 Source #

Deprecated: use offsetInBytes

primOffsetRecast :: forall a b. (PrimType a, PrimType b) => Offset a -> Offset b Source #

sizeRecast :: forall a b. (PrimType a, PrimType b) => CountOf a -> CountOf b Source #

Cast a CountOf linked to type A (CountOf A) to a CountOf linked to type B (CountOf B)