basement-0.0.9: 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 # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Char :: Nat Source #

PrimType Double Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Double :: Nat Source #

PrimType Float Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Float :: Nat Source #

PrimType Int Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int :: Nat Source #

PrimType Int8 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int8 :: Nat Source #

PrimType Int16 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int16 :: Nat Source #

PrimType Int32 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int32 :: Nat Source #

PrimType Int64 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Int64 :: Nat Source #

PrimType Word Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word :: Nat Source #

PrimType Word8 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word8 :: Nat Source #

PrimType Word16 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word16 :: Nat Source #

PrimType Word32 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word32 :: Nat Source #

PrimType Word64 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word64 :: Nat Source #

PrimType CChar Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize CChar :: Nat Source #

PrimType CUChar Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize CUChar :: Nat Source #

PrimType Char7 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Char7 :: Nat Source #

PrimType Word128 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word128 :: Nat Source #

PrimType Word256 Source # 
Instance details

Defined in Basement.PrimType

Associated Types

type PrimSize Word256 :: Nat Source #

PrimType a => PrimType (BE a) Source # 
Instance details

Defined in Basement.PrimType

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 # 
Instance details

Defined in Basement.PrimType

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 #

class PrimMemoryComparable ty Source #

A constraint class for serializable type that have an unique memory compare representation

e.g. Float and Double have -0.0 and 0.0 which are Eq individual, yet have a different memory representation which doesn't allow for memcmp operation

Instances
PrimMemoryComparable Char Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Int Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Int8 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Int16 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Int32 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Int64 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word8 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word16 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word32 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word64 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable CChar Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable CUChar Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word128 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable Word256 Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable a => PrimMemoryComparable (BE a) Source # 
Instance details

Defined in Basement.PrimType

PrimMemoryComparable a => PrimMemoryComparable (LE a) Source # 
Instance details

Defined in Basement.PrimType

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)