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 PrimArray (p :: Pinned) e = PrimArray (Bytes p)
- newtype MPrimArray (p :: Pinned) e s = MPrimArray (MBytes p s)
- data Pinned
- fromBytesPrimArray :: Bytes p -> PrimArray p e
- toBytesPrimArray :: PrimArray p e -> Bytes p
- castPrimArray :: PrimArray p e' -> PrimArray p e
- fromMBytesMPrimArray :: MBytes p s -> MPrimArray p e s
- toMBytesMPrimArray :: MPrimArray p e s -> MBytes p s
- castMPrimArray :: MPrimArray p e' s -> MPrimArray p e s
- allocMPrimArray :: forall e p m s. (Typeable p, Prim e, MonadPrim s m) => Size -> m (MPrimArray p e s)
- allocPinnedMPrimArray :: forall e m s. (MonadPrim s m, Prim e) => Size -> m (MPrimArray Pin e s)
- allocAlignedMPrimArray :: (MonadPrim s m, Prim e) => Count e -> m (MPrimArray Pin e s)
- allocUnpinnedMPrimArray :: forall e m s. (MonadPrim s m, Prim e) => Size -> m (MPrimArray Inc e s)
- shrinkMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => MPrimArray p e s -> Size -> m ()
- resizeMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => MPrimArray p e s -> Size -> m (MPrimArray Inc e s)
- reallocMPrimArray :: forall e p m s. (MonadPrim s m, Typeable p, Prim e) => MPrimArray p e s -> Size -> m (MPrimArray p e s)
- isPinnedPrimArray :: PrimArray p e -> Bool
- isPinnedMPrimArray :: MPrimArray p e s -> Bool
- thawPrimArray :: MonadPrim s m => PrimArray p e -> m (MPrimArray p e s)
- freezeMPrimArray :: MonadPrim s m => MPrimArray p e s -> m (PrimArray p e)
- sizePrimArray :: forall e p. Prim e => PrimArray p e -> Size
- getSizeMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => MPrimArray p e s -> m Size
- readMPrimArray :: (MonadPrim s m, Prim e) => MPrimArray p e s -> Int -> m e
- writeMPrimArray :: (MonadPrim s m, Prim e) => MPrimArray p e s -> Int -> e -> m ()
- setMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => MPrimArray p e s -> Int -> Size -> e -> m ()
- copyPrimArrayToMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => PrimArray p e -> Int -> MPrimArray p e s -> Int -> Size -> m ()
- moveMPrimArrayToMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => MPrimArray p e s -> Int -> MPrimArray p e s -> Int -> Size -> m ()
Documentation
newtype PrimArray (p :: Pinned) e Source #
An immutable array of bytes of type e
Instances
newtype MPrimArray (p :: Pinned) e s Source #
A mutable array of bytes of type e
MPrimArray (MBytes p s) |
Instances
In GHC there is a distinction between pinned and unpinned memory.
Pinned memory is such that 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 the associated ByteArray#
or MutableByteArray#
is no
longer referenced anywhere in the program at which point it gets garbage collected. On
the other hand unpinned memory 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
threshold (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
fromBytesPrimArray :: Bytes p -> PrimArray p e Source #
toBytesPrimArray :: PrimArray p e -> Bytes p Source #
castPrimArray :: PrimArray p e' -> PrimArray p e Source #
fromMBytesMPrimArray :: MBytes p s -> MPrimArray p e s Source #
toMBytesMPrimArray :: MPrimArray p e s -> MBytes p s Source #
castMPrimArray :: MPrimArray p e' s -> MPrimArray p e s Source #
allocMPrimArray :: forall e p m s. (Typeable p, Prim e, MonadPrim s m) => Size -> m (MPrimArray p e s) Source #
allocPinnedMPrimArray :: forall e m s. (MonadPrim s m, Prim e) => Size -> m (MPrimArray Pin e s) Source #
allocAlignedMPrimArray Source #
:: (MonadPrim s m, Prim e) | |
=> Count e | Size in number of bytes |
-> m (MPrimArray Pin e s) |
allocUnpinnedMPrimArray :: forall e m s. (MonadPrim s m, Prim e) => Size -> m (MPrimArray Inc e s) Source #
shrinkMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => MPrimArray 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 getCountMPrimArray
.
resizeMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => MPrimArray p e s -> Size -> m (MPrimArray 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
reallocMPrimArray :: forall e p m s. (MonadPrim s m, Typeable p, Prim e) => MPrimArray p e s -> Size -> m (MPrimArray p e s) Source #
isPinnedPrimArray :: PrimArray p e -> Bool Source #
isPinnedMPrimArray :: MPrimArray p e s -> Bool Source #
thawPrimArray :: MonadPrim s m => PrimArray p e -> m (MPrimArray p e s) Source #
freezeMPrimArray :: MonadPrim s m => MPrimArray p e s -> m (PrimArray p e) Source #
getSizeMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => MPrimArray p e s -> m Size Source #
readMPrimArray :: (MonadPrim s m, Prim e) => MPrimArray p e s -> Int -> m e Source #
writeMPrimArray :: (MonadPrim s m, Prim e) => MPrimArray p e s -> Int -> e -> m () Source #
:: (MonadPrim s m, Prim e) | |
=> MPrimArray 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 () |
copyPrimArrayToMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => PrimArray p e -> Int -> MPrimArray p e s -> Int -> Size -> m () Source #
moveMPrimArrayToMPrimArray :: forall e p m s. (MonadPrim s m, Prim e) => MPrimArray p e s -> Int -> MPrimArray p e s -> Int -> Size -> m () Source #