Copyright | (c) Alexey Kuleshevich 2020 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- newtype ByteArray (p :: Pinned) e = ByteArray (Bytes p)
- newtype MByteArray (p :: Pinned) e s = MByteArray (MBytes p s)
- data Pinned
- fromBytesByteArray :: Bytes p -> ByteArray p e
- toBytesByteArray :: ByteArray p e -> Bytes p
- castByteArray :: ByteArray p e' -> ByteArray p e
- fromMBytesMByteArray :: MBytes p s -> MByteArray p e s
- toMBytesMByteArray :: MByteArray p e s -> MBytes p s
- castMByteArray :: MByteArray p e' s -> MByteArray p e s
- allocMByteArray :: forall e p m s. (Typeable p, Prim e, MonadPrim s m) => Size -> m (MByteArray p e s)
- allocPinnedMByteArray :: forall e m s. (MonadPrim s m, Prim e) => Size -> m (MByteArray Pin e s)
- allocAlignedMByteArray :: (MonadPrim s m, Prim e) => Count e -> m (MByteArray Pin e s)
- allocUnpinnedMByteArray :: forall e m s. (MonadPrim s m, Prim e) => Size -> m (MByteArray Inc e s)
- shrinkMByteArray :: forall e p m s. (MonadPrim s m, Prim e) => MByteArray p e s -> Size -> m ()
- resizeMByteArray :: forall e p m s. (MonadPrim s m, Prim e) => MByteArray p e s -> Size -> m (MByteArray Inc e s)
- reallocMByteArray :: forall e p m s. (MonadPrim s m, Typeable p, Prim e) => MByteArray p e s -> Size -> m (MByteArray p e s)
- isPinnedByteArray :: ByteArray p e -> Bool
- isPinnedMByteArray :: MByteArray p e s -> Bool
- thawByteArray :: MonadPrim s m => ByteArray p e -> m (MByteArray p e s)
- freezeMByteArray :: MonadPrim s m => MByteArray p e s -> m (ByteArray p e)
- sizeByteArray :: forall e p. Prim e => ByteArray p e -> Size
- getSizeMByteArray :: forall e p m s. (MonadPrim s m, Prim e) => MByteArray p e s -> m Size
- readMByteArray :: (MonadPrim s m, Prim e) => MByteArray p e s -> Int -> m e
- writeMByteArray :: (MonadPrim s m, Prim e) => MByteArray p e s -> Int -> e -> m ()
- setMByteArray :: (MonadPrim s m, Prim e) => MByteArray p e s -> Int -> Size -> e -> m ()
- copyByteArrayToMByteArray :: (MonadPrim s m, Prim e) => ByteArray p e -> Int -> MByteArray p e s -> Int -> Size -> m ()
- moveMByteArrayToMByteArray :: forall e p m s. (MonadPrim s m, Prim e) => MByteArray p e s -> Int -> MByteArray p e s -> Int -> Size -> m ()
Documentation
newtype ByteArray (p :: Pinned) e Source #
An immutable array of bytes of type e
Instances
newtype MByteArray (p :: Pinned) e s Source #
A mutable array of bytes of type e
MByteArray (MBytes p s) |
Instances
In Haskell there is a distinction between pinned or unpinned memory.
Pinned memory is such, when allocated, it is guaranteed not to move throughout the lifetime of a program. In other words the address pointer that refers to allocated bytes will not change until it gets garbage collected because it is no longer referenced by anything. Unpinned memory on the other hand can be moved around during GC, which helps to reduce memory fragmentation.
Pinned/unpinnned choice during allocation is a bit of a lie, because when attempt is
made to allocate memory as unpinned, but requested size is a bit more than a certain
threashold (somewhere around 3KiB) it might still be allocated as pinned. Because of
that fact through out the "primal" universe there is a distinction between memory that
is either
or Pin
ned
.Inc
onclusive
It is possible to use one of toPinnedBytes
or
toPinnedMBytes
to get a conclusive type.
Since: 0.1.0
fromBytesByteArray :: Bytes p -> ByteArray p e Source #
toBytesByteArray :: ByteArray p e -> Bytes p Source #
castByteArray :: ByteArray p e' -> ByteArray p e Source #
fromMBytesMByteArray :: MBytes p s -> MByteArray p e s Source #
toMBytesMByteArray :: MByteArray p e s -> MBytes p s Source #
castMByteArray :: MByteArray p e' s -> MByteArray p e s Source #
allocMByteArray :: forall e p m s. (Typeable p, Prim e, MonadPrim s m) => Size -> m (MByteArray p e s) Source #
allocPinnedMByteArray :: forall e m s. (MonadPrim s m, Prim e) => Size -> m (MByteArray Pin e s) Source #
allocAlignedMByteArray Source #
:: (MonadPrim s m, Prim e) | |
=> Count e | Size in number of bytes |
-> m (MByteArray Pin e s) |
allocUnpinnedMByteArray :: forall e m s. (MonadPrim s m, Prim e) => Size -> m (MByteArray Inc e s) Source #
shrinkMByteArray :: forall e p m s. (MonadPrim s m, Prim e) => MByteArray p e s -> Size -> m () Source #
Shrink mutable bytes to new specified count of elements. The new count must be less
than or equal to the current count as reported by getCountMByteArray
.
resizeMByteArray :: forall e p m s. (MonadPrim s m, Prim e) => MByteArray p e s -> Size -> m (MByteArray Inc e s) Source #
Attempt to resize mutable bytes in place.
- New bytes might be allocated, with the copy of an old one.
- Old references should not be kept around to allow GC to claim it
- Old references should not be used to avoid undefined behavior
reallocMByteArray :: forall e p m s. (MonadPrim s m, Typeable p, Prim e) => MByteArray p e s -> Size -> m (MByteArray p e s) Source #
isPinnedByteArray :: ByteArray p e -> Bool Source #
isPinnedMByteArray :: MByteArray p e s -> Bool Source #
thawByteArray :: MonadPrim s m => ByteArray p e -> m (MByteArray p e s) Source #
freezeMByteArray :: MonadPrim s m => MByteArray p e s -> m (ByteArray p e) Source #
getSizeMByteArray :: forall e p m s. (MonadPrim s m, Prim e) => MByteArray p e s -> m Size Source #
readMByteArray :: (MonadPrim s m, Prim e) => MByteArray p e s -> Int -> m e Source #
writeMByteArray :: (MonadPrim s m, Prim e) => MByteArray p e s -> Int -> e -> m () Source #
:: (MonadPrim s m, Prim e) | |
=> MByteArray p e s | Chunk of memory to fill |
-> Int | Offset in number of elements |
-> Size | Number of cells to fill |
-> e | A value to fill the cells with |
-> m () |
copyByteArrayToMByteArray :: (MonadPrim s m, Prim e) => ByteArray p e -> Int -> MByteArray p e s -> Int -> Size -> m () Source #
moveMByteArrayToMByteArray :: forall e p m s. (MonadPrim s m, Prim e) => MByteArray p e s -> Int -> MByteArray p e s -> Int -> Size -> m () Source #