primal-memory-0.1.0.0: Unified interface for memory managemenet.

Copyright(c) Alexey Kuleshevich 2020
LicenseBSD3
MaintainerAlexey Kuleshevich <alexey@kuleshevi.ch>
Stabilityexperimental
Portabilitynon-portable
Safe HaskellNone
LanguageHaskell2010

Data.Prim.Memory.ByteArray

Description

 
Synopsis

Documentation

newtype ByteArray (p :: Pinned) e Source #

An immutable array of bytes of type e

Constructors

ByteArray (Bytes p) 
Instances
PtrAccess s (ByteArray Pin e) Source #

Read-only access, but it is not enforced.

Instance details

Defined in Data.Prim.Memory.ByteArray

Methods

toForeignPtr :: MonadPrim s m => ByteArray Pin e -> m (ForeignPtr a) Source #

withPtrAccess :: MonadPrim s m => ByteArray Pin e -> (Ptr a -> m b) -> m b Source #

withNoHaltPtrAccess :: MonadUnliftPrim s m => ByteArray Pin e -> (Ptr a -> m b) -> m b Source #

(Typeable p, Prim e) => IsList (ByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Associated Types

type Item (ByteArray p e) :: Type #

Methods

fromList :: [Item (ByteArray p e)] -> ByteArray p e #

fromListN :: Int -> [Item (ByteArray p e)] -> ByteArray p e #

toList :: ByteArray p e -> [Item (ByteArray p e)] #

(Show e, Prim e) => Show (ByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Methods

showsPrec :: Int -> ByteArray p e -> ShowS #

show :: ByteArray p e -> String #

showList :: [ByteArray p e] -> ShowS #

Typeable p => IsString (ByteArray p Char) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Typeable p => Semigroup (ByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Methods

(<>) :: ByteArray p e -> ByteArray p e -> ByteArray p e #

sconcat :: NonEmpty (ByteArray p e) -> ByteArray p e #

stimes :: Integral b => b -> ByteArray p e -> ByteArray p e #

Typeable p => Monoid (ByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Methods

mempty :: ByteArray p e #

mappend :: ByteArray p e -> ByteArray p e -> ByteArray p e #

mconcat :: [ByteArray p e] -> ByteArray p e #

NFData (ByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Methods

rnf :: ByteArray p e -> () #

MemRead (ByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Methods

byteCountMem :: ByteArray p e -> Count Word8 Source #

indexOffMem :: Prim e0 => ByteArray p e -> Off e0 -> e0 Source #

indexByteOffMem :: Prim e0 => ByteArray p e -> Off Word8 -> e0 Source #

copyByteOffToMBytesMem :: (MonadPrim s m, Prim e0) => ByteArray p e -> Off Word8 -> MBytes p0 s -> Off Word8 -> Count e0 -> m () Source #

copyByteOffToPtrMem :: (MonadPrim s m, Prim e0) => ByteArray p e -> Off Word8 -> Ptr e0 -> Off Word8 -> Count e0 -> m () Source #

compareByteOffToPtrMem :: (MonadPrim s m, Prim e0) => ByteArray p e -> Off Word8 -> Ptr e0 -> Off Word8 -> Count e0 -> m Ordering Source #

compareByteOffToBytesMem :: (MonadPrim s m, Prim e0) => ByteArray p e -> Off Word8 -> Bytes p0 -> Off Word8 -> Count e0 -> m Ordering Source #

compareByteOffMem :: (MemRead r', Prim e0) => r' -> Off Word8 -> ByteArray p e -> Off Word8 -> Count e0 -> Ordering Source #

type Item (ByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

type Item (ByteArray p e) = e

newtype MByteArray (p :: Pinned) e s Source #

A mutable array of bytes of type e

Constructors

MByteArray (MBytes p s) 
Instances
PtrAccess s (MByteArray Pin e s) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Methods

toForeignPtr :: MonadPrim s m => MByteArray Pin e s -> m (ForeignPtr a) Source #

withPtrAccess :: MonadPrim s m => MByteArray Pin e s -> (Ptr a -> m b) -> m b Source #

withNoHaltPtrAccess :: MonadUnliftPrim s m => MByteArray Pin e s -> (Ptr a -> m b) -> m b Source #

MemWrite (MByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Methods

readOffMem :: (MonadPrim s m, Prim e0) => MByteArray p e s -> Off e0 -> m e0 Source #

readByteOffMem :: (MonadPrim s m, Prim e0) => MByteArray p e s -> Off Word8 -> m e0 Source #

writeOffMem :: (MonadPrim s m, Prim e0) => MByteArray p e s -> Off e0 -> e0 -> m () Source #

writeByteOffMem :: (MonadPrim s m, Prim e0) => MByteArray p e s -> Off Word8 -> e0 -> m () Source #

moveByteOffToMBytesMem :: (MonadPrim s m, Prim e0) => MByteArray p e s -> Off Word8 -> MBytes p0 s -> Off Word8 -> Count e0 -> m () Source #

moveByteOffToPtrMem :: (MonadPrim s m, Prim e0) => MByteArray p e s -> Off Word8 -> Ptr e0 -> Off Word8 -> Count e0 -> m () Source #

copyByteOffMem :: (MonadPrim s m, MemRead r, Prim e0) => r -> Off Word8 -> MByteArray p e s -> Off Word8 -> Count e0 -> m () Source #

moveByteOffMem :: (MonadPrim s m, MemWrite w', Prim e0) => w' s -> Off Word8 -> MByteArray p e s -> Off Word8 -> Count e0 -> m () Source #

setMem :: (MonadPrim s m, Prim e0) => MByteArray p e s -> Off e0 -> Count e0 -> e0 -> m () Source #

Typeable p => MemAlloc (MByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Associated Types

type FrozenMem (MByteArray p e) = (fa :: Type) Source #

Methods

getByteCountMem :: MonadPrim s m => MByteArray p e s -> m (Count Word8) Source #

allocByteCountMem :: MonadPrim s m => Count Word8 -> m (MByteArray p e s) Source #

thawMem :: MonadPrim s m => FrozenMem (MByteArray p e) -> m (MByteArray p e s) Source #

freezeMem :: MonadPrim s m => MByteArray p e s -> m (FrozenMem (MByteArray p e)) Source #

resizeMem :: (MonadPrim s m, Prim e0) => MByteArray p e s -> Count e0 -> m (MByteArray p e s) Source #

NFData (MByteArray p e s) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

Methods

rnf :: MByteArray p e s -> () #

type FrozenMem (MByteArray p e) Source # 
Instance details

Defined in Data.Prim.Memory.ByteArray

type FrozenMem (MByteArray p e) = ByteArray p e

data Pinned Source #

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 Pinned or Inconclusive.

It is possible to use one of toPinnedBytes or toPinnedMBytes to get a conclusive type.

Since: 0.1.0

Constructors

Pin 
Inc 

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 #

Arguments

:: (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 #

thawByteArray :: MonadPrim s m => ByteArray p e -> m (MByteArray p e s) Source #

sizeByteArray :: forall e p. Prim e => ByteArray p e -> Size 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 #

setMByteArray Source #

Arguments

:: (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 #