Copyright | (c) Alexey Kuleshevich 2020 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- class Prim a where
- type PrimBase a :: *
- type SizeOf a :: Nat
- type Alignment a :: Nat
- toPrimBase :: a -> PrimBase a
- fromPrimBase :: PrimBase a -> a
- sizeOf# :: Proxy# a -> Int#
- alignment# :: Proxy# a -> Int#
- indexByteOffByteArray# :: ByteArray# -> Int# -> a
- indexByteArray# :: ByteArray# -> Int# -> a
- indexOffAddr# :: Addr# -> Int# -> a
- readByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
- readMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, a #)
- readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, a #)
- writeByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> a -> State# s -> State# s
- writeMutableByteArray# :: MutableByteArray# s -> Int# -> a -> State# s -> State# s
- writeOffAddr# :: Addr# -> Int# -> a -> State# s -> State# s
- setMutableByteArray# :: MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s
- setOffAddr# :: Addr# -> Int# -> Int# -> a -> State# s -> State# s
- setMutableByteArrayLoop# :: Prim a => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s
- setOffAddrLoop# :: Prim a => Addr# -> Int# -> Int# -> a -> State# s -> State# s
- errorImpossible :: String -> String -> a
- bool2Int# :: Bool -> Int#
- int2Bool# :: Int# -> Bool
- newtype WordPtr = WordPtr Word
- ptrToWordPtr :: Ptr a -> WordPtr
- wordPtrToPtr :: WordPtr -> Ptr a
- newtype IntPtr = IntPtr Int
- ptrToIntPtr :: Ptr a -> IntPtr
- intPtrToPtr :: IntPtr -> Ptr a
Documentation
Invariants:
- Reading should never fail on memory that contains only zeros
- Writing should always overwrite all of the bytes allocated for the element. In other words, writing to a dirty (uninitilized) region of memory should never leave any garbage around. For example, if a type requires 31 bytes of memory then on any write all 31 bytes must be overwritten.
- A single thread write/read sequence must always roundtrip
- This is not a class for serialization, therefore memory layout of unpacked datatype
is selfcontained in
Prim
class and representation is not expected to stay the same between different versions of software. Primitive types likeInt
,Word
,Char
are an exception to this rule for obvious reasons.
Nothing
toPrimBase :: a -> PrimBase a Source #
fromPrimBase :: PrimBase a -> a Source #
sizeOf# :: Proxy# a -> Int# Source #
Returned value must match the SizeOf
type level Nat
alignment# :: Proxy# a -> Int# Source #
Returned value must match the Alignment
type level Nat
indexByteOffByteArray# :: ByteArray# -> Int# -> a Source #
default indexByteOffByteArray# :: Prim (PrimBase a) => ByteArray# -> Int# -> a Source #
indexByteArray# :: ByteArray# -> Int# -> a Source #
default indexByteArray# :: Prim (PrimBase a) => ByteArray# -> Int# -> a Source #
indexOffAddr# :: Addr# -> Int# -> a Source #
readByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) Source #
default readByteOffMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) Source #
readMutableByteArray# :: MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) Source #
default readMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> State# s -> (# State# s, a #) Source #
readOffAddr# :: Addr# -> Int# -> State# s -> (# State# s, a #) Source #
default readOffAddr# :: Prim (PrimBase a) => Addr# -> Int# -> State# s -> (# State# s, a #) Source #
writeByteOffMutableByteArray# :: MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #
default writeByteOffMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #
writeMutableByteArray# :: MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #
default writeMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> a -> State# s -> State# s Source #
writeOffAddr# :: Addr# -> Int# -> a -> State# s -> State# s Source #
setMutableByteArray# :: MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s Source #
Set the region of MutableByteArray to the same value. Offset is in number of elements
default setMutableByteArray# :: Prim (PrimBase a) => MutableByteArray# s -> Int# -> Int# -> a -> State# s -> State# s Source #
setOffAddr# :: Addr# -> Int# -> Int# -> a -> State# s -> State# s Source #
Set the region of memory to the same value. Offset is in number of elements