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
- newtype Atom a = Atom {
- unAtom :: a
- class (Prim a, Eq a) => Atomic a
- class Atomic a => AtomicCount a
- class (Bits a, Atomic a) => AtomicBits a
- class MonadThrow m => MonadPrim s m | m -> s
- type RW = RealWorld
- data RealWorld :: Type
- byteCount :: forall a. Prim a => a -> Count Word8
- byteCountType :: forall a. Prim a => Count Word8
- byteCountProxy :: forall proxy a. Prim a => proxy a -> Count Word8
- alignment :: forall a. Prim a => a -> Int
- alignmentType :: forall a. Prim a => Int
- alignmentProxy :: forall proxy a. Prim a => proxy a -> Int
- newtype Size = Size {}
- newtype Count a = Count {}
- fromCount :: Prim a => Count a -> Int
- toByteCount :: Prim a => Count a -> Count Word8
- fromCount# :: Prim a => Count a -> Int#
- fromByteCount :: forall a. Prim a => Count Word8 -> Count a
- fromByteCountRem :: forall a. Prim a => Count Word8 -> (Count a, Count Word8)
- countAsProxy :: proxy a -> Count a -> Count a
- newtype Off a = Off {}
- toByteOff :: Prim e => Off e -> Off Word8
- fromOff# :: Prim a => Off a -> Int#
- fromByteOff :: forall a. Prim a => Off Word8 -> Off a
- fromByteOffRem :: forall a. Prim a => Off Word8 -> (Off a, Off Word8)
- offAsProxy :: proxy a -> Off a -> Off a
- prefetchValue0 :: MonadPrim s m => a -> m ()
- prefetchValue1 :: MonadPrim s m => a -> m ()
- prefetchValue2 :: MonadPrim s m => a -> m ()
- prefetchValue3 :: MonadPrim s m => a -> m ()
- module Data.Word
- module Data.Int
- data Ptr a
- data ForeignPtr a
- class Typeable (a :: k)
- data Proxy (t :: k) :: forall k. k -> Type = Proxy
- module Data.Monoid
- module Data.Coerce
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.