Copyright | (c) Alexey Kuleshevich 2020 |
---|---|
License | BSD3 |
Maintainer | Alexey Kuleshevich <alexey@kuleshevi.ch> |
Stability | experimental |
Portability | non-portable |
Safe Haskell | None |
Language | Haskell2010 |
Synopsis
- data Bytes (p :: Pinned) = Bytes ByteArray#
- data MBytes (p :: Pinned) s = MBytes (MutableByteArray# s)
- data Pinned
- data MMemView a s = MMemView {}
- data MemView a = MemView {}
- newtype MemState a s = MemState {
- unMemState :: a
- class MemWrite w where
- readOffMem :: (MonadPrim s m, Prim e) => w s -> Off e -> m e
- readByteOffMem :: (MonadPrim s m, Prim e) => w s -> Off Word8 -> m e
- writeOffMem :: (MonadPrim s m, Prim e) => w s -> Off e -> e -> m ()
- writeByteOffMem :: (MonadPrim s m, Prim e) => w s -> Off Word8 -> e -> m ()
- moveByteOffToMBytesMem :: (MonadPrim s m, Prim e) => w s -> Off Word8 -> MBytes p s -> Off Word8 -> Count e -> m ()
- moveByteOffToPtrMem :: (MonadPrim s m, Prim e) => w s -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m ()
- copyByteOffMem :: (MonadPrim s m, MemRead r, Prim e) => r -> Off Word8 -> w s -> Off Word8 -> Count e -> m ()
- moveByteOffMem :: (MonadPrim s m, MemWrite w', Prim e) => w' s -> Off Word8 -> w s -> Off Word8 -> Count e -> m ()
- setMem :: (MonadPrim s m, Prim e) => w s -> Off e -> Count e -> e -> m ()
- class (MemRead (FrozenMem a), MemWrite a) => MemAlloc a where
- type FrozenMem a = (fa :: Type) | fa -> a
- getByteCountMem :: MonadPrim s m => a s -> m (Count Word8)
- allocByteCountMem :: MonadPrim s m => Count Word8 -> m (a s)
- thawMem :: MonadPrim s m => FrozenMem a -> m (a s)
- freezeMem :: MonadPrim s m => a s -> m (FrozenMem a)
- resizeMem :: (MonadPrim s m, Prim e) => a s -> Count e -> m (a s)
- class MemRead r where
- byteCountMem :: r -> Count Word8
- indexOffMem :: Prim e => r -> Off e -> e
- indexByteOffMem :: Prim e => r -> Off Word8 -> e
- copyByteOffToMBytesMem :: (MonadPrim s m, Prim e) => r -> Off Word8 -> MBytes p s -> Off Word8 -> Count e -> m ()
- copyByteOffToPtrMem :: (MonadPrim s m, Prim e) => r -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m ()
- compareByteOffToPtrMem :: (MonadPrim s m, Prim e) => r -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m Ordering
- compareByteOffToBytesMem :: (MonadPrim s m, Prim e) => r -> Off Word8 -> Bytes p -> Off Word8 -> Count e -> m Ordering
- compareByteOffMem :: (MemRead r', Prim e) => r' -> Off Word8 -> r -> Off Word8 -> Count e -> Ordering
- modifyFetchOldMem :: (MemWrite w, MonadPrim s m, Prim b) => w s -> Off b -> (b -> b) -> m b
- modifyFetchNewMem :: (MemWrite w, MonadPrim s m, Prim b) => w s -> Off b -> (b -> b) -> m b
- modifyFetchOldMemM :: (MemWrite w, MonadPrim s m, Prim b) => w s -> Off b -> (b -> m b) -> m b
- modifyFetchNewMemM :: (MemWrite w, MonadPrim s m, Prim b) => w s -> Off b -> (b -> m b) -> m b
- defaultResizeMem :: (Prim e, MemAlloc a, MonadPrim s m) => a s -> Count e -> m (a s)
- cycleMemN :: (MemAlloc a, MemRead r) => Int -> r -> FrozenMem a
- emptyMem :: MemAlloc a => FrozenMem a
- singletonMem :: forall e a. (MemAlloc a, Prim e) => e -> FrozenMem a
- allocMem :: (MemAlloc a, MonadPrim s m, Prim e) => Count e -> m (a s)
- allocZeroMem :: (MemAlloc a, MonadPrim s m, Prim e) => Count e -> m (a s)
- createMemST :: (MemAlloc a, Prim e) => Count e -> (forall s. a s -> ST s b) -> (b, FrozenMem a)
- createMemST_ :: (MemAlloc a, Prim e) => Count e -> (forall s. a s -> ST s b) -> FrozenMem a
- createZeroMemST :: (MemAlloc a, Prim e) => Count e -> (forall s. a s -> ST s b) -> (b, FrozenMem a)
- createZeroMemST_ :: (MemAlloc a, Prim e) => Count e -> (forall s. a s -> ST s b) -> FrozenMem a
- copyMem :: (MonadPrim s m, MemRead r, MemWrite w, Prim e) => r -> Off e -> w s -> Off e -> Count e -> m ()
- moveMem :: (MonadPrim s m, MemWrite w1, MemWrite w2, Prim e) => w1 s -> Off e -> w2 s -> Off e -> Count e -> m ()
- appendMem :: (MemRead r1, MemRead r2, MemAlloc a) => r1 -> r2 -> FrozenMem a
- concatMem :: (MemRead r, MemAlloc a) => [r] -> FrozenMem a
- thawCopyMem :: (MemRead r, MemAlloc a, MonadPrim s m, Prim e) => r -> Off e -> Count e -> m (a s)
- freezeCopyMem :: (MemAlloc a, MonadPrim s m, Prim e) => a s -> Off e -> Count e -> m (FrozenMem a)
- thawCloneMem :: (MemRead r, MemAlloc a, MonadPrim s m) => r -> m (a s)
- freezeCloneMem :: (MemAlloc a, MonadPrim s m) => a s -> m (FrozenMem a)
- convertMem :: (MemRead r, MemAlloc a) => r -> FrozenMem a
- countMem :: forall e r. (MemRead r, Prim e) => r -> Count e
- countRemMem :: forall e r. (MemRead r, Prim e) => r -> (Count e, Count Word8)
- getCountMem :: (MemAlloc r, MonadPrim s m, Prim e) => r s -> m (Count e)
- getCountRemMem :: (MemAlloc r, MonadPrim s m, Prim e) => r s -> m (Count e, Count Word8)
- clone :: (MemAlloc r, MonadPrim s m) => r s -> m (r s)
- eqMem :: (MemRead r1, MemRead r2) => r1 -> r2 -> Bool
- compareMem :: (MemRead r1, MemRead r2, Prim e) => r1 -> Off e -> r2 -> Off e -> Count e -> Ordering
- toListMem :: (MemRead r, Prim e) => r -> [e]
- toListSlackMem :: forall e r. (MemRead r, Prim e) => r -> ([e], [Word8])
- foldrCountMem :: (MemRead r, Prim e) => Count e -> (e -> b -> b) -> b -> r -> b
- loadListMemN :: (MemWrite r, MonadPrim s m, Prim e) => Count e -> Count Word8 -> [e] -> r s -> m Ordering
- loadListMemN_ :: (MemWrite r, MonadPrim s m, Prim e) => Count e -> [e] -> r s -> m ()
- loadListMem :: (MonadPrim s m, MemAlloc r, Prim e) => [e] -> r s -> m Ordering
- loadListMem_ :: (MonadPrim s m, MemAlloc r, Prim e) => [e] -> r s -> m ()
- fromListMemN :: (MemAlloc a, Prim e) => Count e -> [e] -> (Ordering, FrozenMem a)
- fromListMemN_ :: (MemAlloc a, Prim e) => Count e -> [e] -> FrozenMem a
- fromListMem :: (MemAlloc a, Prim e) => [e] -> FrozenMem a
- fromByteListMem :: MemAlloc a => [Word8] -> FrozenMem a
- toByteListMem :: MemAlloc a => FrozenMem a -> [Word8]
- mapByteMem :: (MemRead r, MemAlloc a, Prim e) => (Word8 -> e) -> r -> FrozenMem a
- mapByteOffMem :: (MemRead r, MemAlloc a, Prim e) => (Off Word8 -> Word8 -> e) -> r -> FrozenMem a
- mapByteMemM :: (MemRead r, MemAlloc a, MonadPrim s m, Prim e) => (Word8 -> m e) -> r -> m (FrozenMem a)
- mapByteOffMemM :: (MemRead r, MemAlloc a, MonadPrim s m, Prim e) => (Off Word8 -> Word8 -> m e) -> r -> m (FrozenMem a)
- forByteOffMemM_ :: (MemRead r, MonadPrim s m, Prim e) => r -> Off Word8 -> Count e -> (Off Word8 -> e -> m b) -> m (Off Word8)
- loopShortM :: Monad m => Int -> (Int -> a -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a
- loopShortM' :: Monad m => Int -> (Int -> a -> m Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a
- izipWithByteOffMemM_ :: (MemRead r1, MemRead r2, MonadPrim s m, Prim e) => r1 -> Off Word8 -> r2 -> Off Word8 -> Count e -> (Off Word8 -> e -> Off Word8 -> e -> m b) -> m (Off Word8)
- izipWithOffMemM_ :: (MemRead r1, MemRead r2, MonadPrim s m, Prim e1, Prim e2) => r1 -> Off e1 -> r2 -> Off e2 -> Int -> (Off e1 -> e1 -> Off e2 -> e2 -> m b) -> m ()
- showsHexMem :: MemRead r => r -> [ShowS]
- withScrubbedMem :: (MonadUnliftPrim RW m, Prim e, MemAlloc mem) => Count e -> (mem RW -> m a) -> m a
Documentation
data Bytes (p :: Pinned) Source #
An immutable region of memory which was allocated either as pinned or unpinned.
Constructor is not exported for safety. Violating type level Pinned
kind is very
dangerous. Type safe constructor fromByteArray#
and unwrapper
toByteArray#
should be used instead. As a backdoor, of course,
the actual constructor is available in Data.Prim.Memory.Internal module and specially
unsafe function castPinnedBytes
was crafted.
Instances
data MBytes (p :: Pinned) s Source #
Mutable region of memory which was allocated either as pinned or unpinned.
Constructor is not exported for safety. Violating type level Pinned
kind is very
dangerous. Type safe constructor fromMutableByteArray#
and
unwrapper toMutableByteArray#
should be used instead. As a
backdoor, of course, the actual constructor is available in Data.Prim.Memory.Internal
module and specially unsafe function castPinnedMBytes
was crafted.
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
A wrapper that adds a phantom state token. It can be use with types that either
doesn't have such state token or are designed to work in IO
and therefore restricted
to RW
. Using this wrapper is very much unsafe, so make sure you know what you are
doing.
MemState | |
|
Instances
class MemWrite w where Source #
readOffMem :: (MonadPrim s m, Prim e) => w s -> Off e -> m e Source #
readByteOffMem :: (MonadPrim s m, Prim e) => w s -> Off Word8 -> m e Source #
writeOffMem :: (MonadPrim s m, Prim e) => w s -> Off e -> e -> m () Source #
writeByteOffMem :: (MonadPrim s m, Prim e) => w s -> Off Word8 -> e -> m () Source #
moveByteOffToMBytesMem :: (MonadPrim s m, Prim e) => w s -> Off Word8 -> MBytes p s -> Off Word8 -> Count e -> m () Source #
Source and target can be overlapping memory chunks
moveByteOffToPtrMem :: (MonadPrim s m, Prim e) => w s -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m () Source #
Source and target can be overlapping memory chunks
copyByteOffMem :: (MonadPrim s m, MemRead r, Prim e) => r -> Off Word8 -> w s -> Off Word8 -> Count e -> m () Source #
moveByteOffMem :: (MonadPrim s m, MemWrite w', Prim e) => w' s -> Off Word8 -> w s -> Off Word8 -> Count e -> m () Source #
:: (MonadPrim s m, Prim e) | |
=> w s | Writable memory. Must have enough bytes, at least: (off+count)*(sizeOf e) |
-> Off e | An offset into writable memory at which element setting should start. |
-> Count e | Numer of cells to write the elemnt into |
-> e | Element to write into all memory cells specified by offset and count. Even
if the count is |
-> m () |
Write the same value into each cell starting at an offset.
Instances
class (MemRead (FrozenMem a), MemWrite a) => MemAlloc a where Source #
Generalized memory allocation and pure/mutable state conversion.
getByteCountMem :: MonadPrim s m => a s -> m (Count Word8) Source #
allocByteCountMem :: MonadPrim s m => Count Word8 -> m (a s) Source #
thawMem :: MonadPrim s m => FrozenMem a -> m (a s) Source #
freezeMem :: MonadPrim s m => a s -> m (FrozenMem a) Source #
resizeMem :: (MonadPrim s m, Prim e) => a s -> Count e -> m (a s) Source #
Instances
class MemRead r where Source #
byteCountMem :: r -> Count Word8 Source #
indexOffMem :: Prim e => r -> Off e -> e Source #
indexByteOffMem :: Prim e => r -> Off Word8 -> e Source #
copyByteOffToMBytesMem :: (MonadPrim s m, Prim e) => r -> Off Word8 -> MBytes p s -> Off Word8 -> Count e -> m () Source #
Source and target can't refer to the same memory chunks
copyByteOffToPtrMem :: (MonadPrim s m, Prim e) => r -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m () Source #
Source and target can't refer to the same memory chunks
compareByteOffToPtrMem :: (MonadPrim s m, Prim e) => r -> Off Word8 -> Ptr e -> Off Word8 -> Count e -> m Ordering Source #
compareByteOffToBytesMem :: (MonadPrim s m, Prim e) => r -> Off Word8 -> Bytes p -> Off Word8 -> Count e -> m Ordering Source #
compareByteOffMem :: (MemRead r', Prim e) => r' -> Off Word8 -> r -> Off Word8 -> Count e -> Ordering Source #
Instances
modifyFetchOldMem :: (MemWrite w, MonadPrim s m, Prim b) => w s -> Off b -> (b -> b) -> m b Source #
modifyFetchNewMem :: (MemWrite w, MonadPrim s m, Prim b) => w s -> Off b -> (b -> b) -> m b Source #
modifyFetchOldMemM :: (MemWrite w, MonadPrim s m, Prim b) => w s -> Off b -> (b -> m b) -> m b Source #
modifyFetchNewMemM :: (MemWrite w, MonadPrim s m, Prim b) => w s -> Off b -> (b -> m b) -> m b Source #
cycleMemN :: (MemAlloc a, MemRead r) => Int -> r -> FrozenMem a Source #
Make n
copies of supplied region of memory into a contiguous chunk of memory.
singletonMem :: forall e a. (MemAlloc a, Prim e) => e -> FrozenMem a Source #
A region of memory that hold a single element.
allocMem :: (MemAlloc a, MonadPrim s m, Prim e) => Count e -> m (a s) Source #
Allocate enough memory for number of elements. Memory is not initialized and may
contain garbage. Use allocZeroMem
if clean memory is needed.
- Unsafe Count
- Negative element count will result in unpredictable behavior
Since: 0.1.0
allocZeroMem :: (MemAlloc a, MonadPrim s m, Prim e) => Count e -> m (a s) Source #
Same as allocMem
, but also use memset
to initialize all the new memory to zeros.
- Unsafe Count
- Negative element count will result in unpredictable behavior
Since: 0.1.0
createMemST :: (MemAlloc a, Prim e) => Count e -> (forall s. a s -> ST s b) -> (b, FrozenMem a) Source #
createMemST_ :: (MemAlloc a, Prim e) => Count e -> (forall s. a s -> ST s b) -> FrozenMem a Source #
createZeroMemST :: (MemAlloc a, Prim e) => Count e -> (forall s. a s -> ST s b) -> (b, FrozenMem a) Source #
createZeroMemST_ :: (MemAlloc a, Prim e) => Count e -> (forall s. a s -> ST s b) -> FrozenMem a Source #
thawCopyMem :: (MemRead r, MemAlloc a, MonadPrim s m, Prim e) => r -> Off e -> Count e -> m (a s) Source #
freezeCopyMem :: (MemAlloc a, MonadPrim s m, Prim e) => a s -> Off e -> Count e -> m (FrozenMem a) Source #
convertMem :: (MemRead r, MemAlloc a) => r -> FrozenMem a Source #
O(n) - Convert a read-only memory region into a newly allocated other type of memory region
>>>
import Data.ByteString
>>>
bs = pack [0x10 .. 0x20]
>>>
bs
"\DLE\DC1\DC2\DC3\DC4\NAK\SYN\ETB\CAN\EM\SUB\ESC\FS\GS\RS\US ">>>
convertMem bs :: Bytes 'Inc
[0x10,0x11,0x12,0x13,0x14,0x15,0x16,0x17,0x18,0x19,0x1a,0x1b,0x1c,0x1d,0x1e,0x1f,0x20]
Since: 0.1.0
Figure out how many elements can fit into the region of memory. It is possible that
there is a remainder of bytes left, see countRemMem
for getting that too.
Examples
>>>
b = fromListMem [0 .. 5 :: Word8] :: Bytes 'Pin
>>>
b
[0x00,0x01,0x02,0x03,0x04,0x05]>>>
countMem b :: Count Word16
Count {unCount = 3}>>>
countMem b :: Count Word32
Count {unCount = 1}
Since: 0.1.0
countRemMem :: forall e r. (MemRead r, Prim e) => r -> (Count e, Count Word8) Source #
Compute how many elements and a byte size remainder that can fit into the region of memory.
Examples
>>>
b = fromListMem [0 .. 5 :: Word8] :: Bytes 'Pin
>>>
b
[0x00,0x01,0x02,0x03,0x04,0x05]>>>
countRemMem @Word16 b
(Count {unCount = 3},0)>>>
countRemMem @Word32 b
(Count {unCount = 1},2)
Since: 0.1.0
:: (MemRead r1, MemRead r2, Prim e) | |
=> r1 | First region of memory |
-> Off e | Offset in number of elements into the first region |
-> r2 | Second region of memory |
-> Off e | Offset in number of elements into the second region |
-> Count e | Number of elements to compare |
-> Ordering |
Compare two regions of memory byte-by-byte. It will return EQ
whenever both regions
are exactly the same and LT
or GT
as soon as the first byte is reached that is less
than or greater than respectfully in the first region when compared to the second
one. It is safe for both regions to refer to the same part of memory, since this is a
pure function and both regions of memory are read-only.
toListMem :: (MemRead r, Prim e) => r -> [e] Source #
It is only guaranteed to convert the whole memory to a list whenever the size of allocated memory is exactly divisible by the size of the element, otherwise there will be some slack left unaccounted for.
toListSlackMem :: forall e r. (MemRead r, Prim e) => r -> ([e], [Word8]) Source #
Same as toListMem
, except if there is some slack at the end of the memory that
didn't fit in a list it will be returned as a list of bytes
Examples
>>>
import Data.Word
>>>
:set -XDataKinds
>>>
a = fromListMem [0 .. 10 :: Word8] :: Bytes 'Pin
>>>
a
[0x00,0x01,0x02,0x03,0x04,0x05,0x06,0x07,0x08,0x09,0x0a]>>>
toListSlackMem a :: ([Word8], [Word8])
([0,1,2,3,4,5,6,7,8,9,10],[])>>>
toListSlackMem a :: ([Word16], [Word8])
([256,770,1284,1798,2312],[10])>>>
toListSlackMem a :: ([Word32], [Word8])
([50462976,117835012],[8,9,10])>>>
toListSlackMem a :: ([Word64], [Word8])
([506097522914230528],[8,9,10])
Since: 0.1.0
foldrCountMem :: (MemRead r, Prim e) => Count e -> (e -> b -> b) -> b -> r -> b Source #
Right fold that is useful for converting to list while tapping into list fusion.
loadListMemN :: (MemWrite r, MonadPrim s m, Prim e) => Count e -> Count Word8 -> [e] -> r s -> m Ordering Source #
fromByteListMem :: MemAlloc a => [Word8] -> FrozenMem a Source #
Load a list of bytes into a newly allocated memory region. Equivalent to
pack
for ByteString
Examples
>>>
fromByteListMem [0..10] :: Bytes 'Pin
[0x00,0x01,0x02,0x03,0x04,0x05,0x06,0x07,0x08,0x09,0x0a]
Since: 0.1.0
toByteListMem :: MemAlloc a => FrozenMem a -> [Word8] Source #
Convert a memory region to a list of bytes. Equivalent to unpack
for ByteString
>>>
toByteListMem (fromByteListMem [0..10] :: Bytes 'Pin)
[0,1,2,3,4,5,6,7,8,9,10]
Since: 0.1.0
mapByteOffMem :: (MemRead r, MemAlloc a, Prim e) => (Off Word8 -> Word8 -> e) -> r -> FrozenMem a Source #
Map an index aware function over memory region
>>>
a = fromListMem [1 .. 10 :: Word8] :: Bytes 'Inc
>>>
a
[0x01,0x02,0x03,0x04,0x05,0x06,0x07,0x08,0x09,0x0a]>>>
imapMem (\i e -> (fromIntegral i :: Int8, e + 0xf0)) a :: Bytes 'Pin
[0x00,0xf1,0x01,0xf2,0x02,0xf3,0x03,0xf4,0x04,0xf5,0x05,0xf6,0x06,0xf7,0x07,0xf8,0x08,0xf9,0x09,0xfa]
Since: 0.1.0
mapByteMemM :: (MemRead r, MemAlloc a, MonadPrim s m, Prim e) => (Word8 -> m e) -> r -> m (FrozenMem a) Source #
mapByteOffMemM :: (MemRead r, MemAlloc a, MonadPrim s m, Prim e) => (Off Word8 -> Word8 -> m e) -> r -> m (FrozenMem a) Source #
forByteOffMemM_ :: (MemRead r, MonadPrim s m, Prim e) => r -> Off Word8 -> Count e -> (Off Word8 -> e -> m b) -> m (Off Word8) Source #
Iterate over a region of memory
loopShortM :: Monad m => Int -> (Int -> a -> Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a Source #
loopShortM' :: Monad m => Int -> (Int -> a -> m Bool) -> (Int -> Int) -> a -> (Int -> a -> m a) -> m a Source #
izipWithByteOffMemM_ :: (MemRead r1, MemRead r2, MonadPrim s m, Prim e) => r1 -> Off Word8 -> r2 -> Off Word8 -> Count e -> (Off Word8 -> e -> Off Word8 -> e -> m b) -> m (Off Word8) Source #
izipWithOffMemM_ :: (MemRead r1, MemRead r2, MonadPrim s m, Prim e1, Prim e2) => r1 -> Off e1 -> r2 -> Off e2 -> Int -> (Off e1 -> e1 -> Off e2 -> e2 -> m b) -> m () Source #
showsHexMem :: MemRead r => r -> [ShowS] Source #
A list of ShowS
that covert bytes to base16 encoded strings. Each element of the list
is a function that will convert one byte.
>>>
mb <- newPinnedMBytes (Count 5 :: Count Int)
>>>
mapM_ (\i -> writeOffMBytes mb (pred i) i) [1 .. 5]
>>>
foldr ($) "" . showsBytesHex <$> freezeMBytes mb
"01000000000000000200000000000000030000000000000004000000000000000500000000000000"
withScrubbedMem :: (MonadUnliftPrim RW m, Prim e, MemAlloc mem) => Count e -> (mem RW -> m a) -> m a Source #
Ensure that memory is filled with zeros before and after it is used.