haskus-binary-1.5: Haskus binary format manipulation

Safe HaskellNone
LanguageHaskell2010

Haskus.Memory.Buffer

Contents

Description

A buffer in memory

Synopsis

Documentation

data Buffer (mut :: Mutability) (pin :: Pinning) (fin :: Finalization) (heap :: Heap) where Source #

A memory buffer

Instances
IsList BufferI Source #

Support for OverloadedLists

>>> :set -XOverloadedLists
>>> let b = [25,26,27,28] :: BufferI
Instance details

Defined in Haskus.Memory.Buffer

Associated Types

type Item BufferI :: Type #

BufferToList BufferPF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferToList BufferF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferToList BufferP Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferToList BufferI Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferEF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferMEF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferPF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferE Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferME Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferP Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferI Source # 
Instance details

Defined in Haskus.Memory.Buffer

MonadIO m => PutMonad (BufferPutT (Buffer Mutable pin gc heap) m) Source # 
Instance details

Defined in Haskus.Binary.Serialize.Buffer

Methods

putWord8 :: Word8 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord16 :: Word16 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord32 :: Word32 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord64 :: Word64 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord8s :: [Word8] -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord16s :: [Word16] -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord32s :: [Word32] -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putWord64s :: [Word64] -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

putBuffer :: BufferSize (Buffer Immutable pin0 gc0 heap0) => Buffer Immutable pin0 gc0 heap0 -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

preAllocateAtLeast :: Word -> BufferPutT (Buffer Mutable pin gc heap) m () Source #

MonadIO m => GetMonad (BufferGetT (Buffer mut pin gc heap) m) Source # 
Instance details

Defined in Haskus.Binary.Serialize.Buffer

Methods

getWord8 :: BufferGetT (Buffer mut pin gc heap) m Word8 Source #

getWord16 :: BufferGetT (Buffer mut pin gc heap) m Word16 Source #

getWord32 :: BufferGetT (Buffer mut pin gc heap) m Word32 Source #

getWord64 :: BufferGetT (Buffer mut pin gc heap) m Word64 Source #

getWord8s :: Word -> BufferGetT (Buffer mut pin gc heap) m [Word8] Source #

getWord16s :: Word -> BufferGetT (Buffer mut pin gc heap) m [Word16] Source #

getWord32s :: Word -> BufferGetT (Buffer mut pin gc heap) m [Word32] Source #

getWord64s :: Word -> BufferGetT (Buffer mut pin gc heap) m [Word64] Source #

getBuffer :: Word -> BufferGetT (Buffer mut pin gc heap) m BufferI Source #

getBufferInto :: Word -> Buffer Mutable pin0 gc0 heap0 -> Maybe Word -> BufferGetT (Buffer mut pin gc heap) m () Source #

getSkipBytes :: Word -> BufferGetT (Buffer mut pin gc heap) m () Source #

Thawable (Buffer Immutable pin NotFinalized heap) (Buffer Mutable pin NotFinalized heap) Source # 
Instance details

Defined in Haskus.Memory.Buffer

Thawable (Buffer Immutable pin Collected heap) (Buffer Mutable pin Collected heap) Source # 
Instance details

Defined in Haskus.Memory.Buffer

Freezable (Buffer Mutable pin fin External) (Buffer Immutable pin fin External) Source # 
Instance details

Defined in Haskus.Memory.Buffer

Freezable (Buffer Mutable pin Collected heap) (Buffer Immutable pin Collected heap) Source # 
Instance details

Defined in Haskus.Memory.Buffer

type Item BufferI Source # 
Instance details

Defined in Haskus.Memory.Buffer

newtype AnyBuffer Source #

Wrapper containing any kind of buffer

Constructors

AnyBuffer (forall mut pin fin heap. Buffer mut pin fin heap) 

Buffer taxonomy

data Pinning Source #

Is the buffer pinned into memory?

Constructors

Pinned

The buffer has a fixed associated memory address

NotPinned

The buffer contents can be freely moved to another address

Instances
Eq Pinning Source # 
Instance details

Defined in Haskus.Memory.Property

Methods

(==) :: Pinning -> Pinning -> Bool #

(/=) :: Pinning -> Pinning -> Bool #

Show Pinning Source # 
Instance details

Defined in Haskus.Memory.Property

data Finalization Source #

Is the memory automatically garbage collected?

Constructors

Collected

Automatically collected by the garbage-collector

Finalized

Finalizers are run just before the garbage collector collects the referencing entity (buffer, pointer...). The memory used by the entity may be collected too (Internal heap), explicitly freed by a finalizer or not freed at all.

NotFinalized

The memory is not automatically freed and we can't attach finalizers to the buffer.

data Mutability Source #

Is the memory mutable or not?

Constructors

Mutable

Memory cells are mutable

Immutable

Memory cells are immutable

Instances
Eq Mutability Source # 
Instance details

Defined in Haskus.Memory.Property

Show Mutability Source # 
Instance details

Defined in Haskus.Memory.Property

data Heap Source #

Allocation heap

Constructors

Internal

GHC heap

External

External heap

GHC allocator

newBuffer :: MonadIO m => Word -> m BufferM Source #

Allocate a buffer (mutable, unpinned)

>>> b <- newBuffer 1024

newPinnedBuffer :: MonadIO m => Word -> m BufferMP Source #

Allocate a buffer (mutable, pinned)

newAlignedPinnedBuffer :: MonadIO m => Word -> Word -> m BufferMP Source #

Allocate an aligned buffer (mutable, pinned)

Buffer size

bufferSizeIO :: MonadIO m => Buffer mut pin fin heap -> m Word Source #

Get buffer size

class BufferSize a where Source #

Methods

bufferSize :: a -> Word Source #

Get buffer size

Instances
BufferSize BufferEF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferMEF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferPF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferE Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferME Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferP Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferSize BufferI Source # 
Instance details

Defined in Haskus.Memory.Buffer

Buffer freeze/thaw

class Freezable a b | a -> b where Source #

Buffer that can be frozen (converted from mutable to immutable)

Methods

unsafeBufferFreeze :: MonadIO m => a -> m b Source #

Convert a mutable buffer to an immutable one without copying. The buffer should not be modified after the conversion.

Instances
Freezable (Buffer Mutable pin fin External) (Buffer Immutable pin fin External) Source # 
Instance details

Defined in Haskus.Memory.Buffer

Freezable (Buffer Mutable pin Collected heap) (Buffer Immutable pin Collected heap) Source # 
Instance details

Defined in Haskus.Memory.Buffer

class Thawable a b | a -> b where Source #

Buffer that can be thawed (converted from immutable to mutable)

Methods

unsafeBufferThaw :: MonadIO m => a -> m b Source #

Convert an immutable buffer to a mutable one without copying. The original buffer should not be used after the conversion.

Instances
Thawable (Buffer Immutable pin NotFinalized heap) (Buffer Mutable pin NotFinalized heap) Source # 
Instance details

Defined in Haskus.Memory.Buffer

Thawable (Buffer Immutable pin Collected heap) (Buffer Mutable pin Collected heap) Source # 
Instance details

Defined in Haskus.Memory.Buffer

Buffer address

bufferIsDynamicallyPinned :: Buffer mut pin fin heap -> Bool Source #

Some buffers managed by GHC can be pinned as an optimization. This function reports this.

bufferDynamicallyPinned :: Buffer mut pin fin heap -> Either (Buffer mut NotPinned fin heap) (Buffer mut Pinned fin heap) Source #

Transform type-level NotPinned buffers into type-level Pinned if the buffer is dynamically pinned (see bufferIsDynamicallyPinned).

withBufferAddr# :: MonadIO m => Buffer Mutable Pinned fin heap -> (Addr# -> m a) -> m a Source #

Do something with a buffer address

withBufferPtr :: MonadIO m => Buffer Mutable Pinned fin heap -> (Ptr b -> m a) -> m a Source #

Do something with a buffer pointer

unsafeWithBufferAddr# :: MonadIO m => Buffer mut Pinned fin heap -> (Addr# -> m a) -> m a Source #

Do something with a buffer address

Note: don't write into immutable buffer as it would break referential consistency

unsafeWithBufferPtr :: MonadIO m => Buffer mut Pinned fin heap -> (Ptr b -> m a) -> m a Source #

Do something with a buffer pointer

Note: don't write into immutable buffer as it would break referential consistency

Buffer read

bufferReadWord8IO :: MonadIO m => Buffer mut pin fin heap -> Word -> m Word8 Source #

Read a Word8, offset in bytes

We don't check that the offset is valid

>>> let b = [25,26,27,28] :: BufferI
>>> bufferReadWord8IO b 2
27

bufferReadWord8 :: Buffer Immutable pin fin heap -> Word -> Word8 Source #

Read a Word8 in an immutable buffer, offset in bytes

We don't check that the offset is valid

>>> let b = [25,26,27,28] :: BufferI
>>> putStrLn $ "Word8 at offset 2 is " ++ show (bufferReadWord8 b 2)
Word8 at offset 2 is 27

bufferReadWord16IO :: MonadIO m => Buffer mut pin fin heap -> Word -> m Word16 Source #

Read a Word16, offset in bytes

We don't check that the offset is valid

>>> let b = [0x12,0x34,0x56,0x78] :: BufferI
>>> x <- bufferReadWord16IO b 0
>>> (x == 0x1234) || (x == 0x3412)
True

bufferReadWord16 :: Buffer Immutable pin fin heap -> Word -> Word16 Source #

Read a Word16 in an immutable buffer, offset in bytes

We don't check that the offset is valid

bufferReadWord32IO :: MonadIO m => Buffer mut pin fin heap -> Word -> m Word32 Source #

Read a Word32, offset in bytes

We don't check that the offset is valid

>>> let b = [0x12,0x34,0x56,0x78] :: BufferI
>>> x <- bufferReadWord32IO b 0
>>> (x == 0x12345678) || (x == 0x78563412)
True

bufferReadWord32 :: Buffer Immutable pin fin heap -> Word -> Word32 Source #

Read a Word32 in an immutable buffer, offset in bytes

We don't check that the offset is valid

bufferReadWord64IO :: MonadIO m => Buffer mut pin fin heap -> Word -> m Word64 Source #

Read a Word64, offset in bytes

We don't check that the offset is valid

>>> let b = [0x12,0x34,0x56,0x78,0x9A,0xBC,0xDE,0xF0] :: BufferI
>>> x <- bufferReadWord64IO b 0
>>> (x == 0x123456789ABCDEF0) || (x == 0xF0DEBC9A78563412)
True

bufferReadWord64 :: Buffer Immutable pin fin heap -> Word -> Word64 Source #

Read a Word64 in an immutable buffer, offset in bytes

We don't check that the offset is valid

Buffer write and copy

bufferWriteWord8IO :: MonadIO m => Buffer Mutable pin fin heap -> Word -> Word8 -> m () Source #

Write a Word8, offset in bytes

We don't check that the offset is valid

>>> b <- newBuffer 10
>>> bufferWriteWord8IO b 1 123
>>> bufferReadWord8IO b 1
123

bufferWriteWord16IO :: MonadIO m => Buffer Mutable pin fin heap -> Word -> Word16 -> m () Source #

Write a Word16, offset in bytes

We don't check that the offset is valid

>>> b <- newBuffer 10
>>> let v = 1234 :: Word16
>>> bufferWriteWord16IO b 1 v
>>> bufferReadWord16IO b 1
1234
>>> (x :: Word16) <- fromIntegral <$> bufferReadWord8IO b 1
>>> (y :: Word16) <- fromIntegral <$> bufferReadWord8IO b 2
>>> (((x `shiftL` 8) .|. y) == v)   ||   (((y `shiftL` 8) .|. x) == v)
True

bufferWriteWord32IO :: MonadIO m => Buffer Mutable pin fin heap -> Word -> Word32 -> m () Source #

Write a Word32, offset in bytes

We don't check that the offset is valid

>>> b <- newBuffer 10
>>> let v = 1234 :: Word32
>>> bufferWriteWord32IO b 1 v
>>> bufferReadWord32IO b 1
1234

bufferWriteWord64IO :: MonadIO m => Buffer Mutable pin fin heap -> Word -> Word64 -> m () Source #

Write a Word64, offset in bytes

We don't check that the offset is valid

>>> b <- newBuffer 10
>>> let v = 1234 :: Word64
>>> bufferWriteWord64IO b 1 v
>>> bufferReadWord64IO b 1
1234

copyBuffer Source #

Arguments

:: MonadIO m 
=> Buffer mut pin0 fin0 heap0

Source buffer

-> Word

Offset in source buffer

-> Buffer Mutable pin1 fin1 heap1

Target buffer

-> Word

Offset in target buffer

-> Word

Number of Word8 to copy

-> m () 

Copy a buffer into another from/to the given offsets

We don't check buffer limits.

>>> let b = [0,1,2,3,4,5,6,7,8] :: BufferI
>>> b2 <- newBuffer 8
>>> copyBuffer b 4 b2 0 4
>>> copyBuffer b 0 b2 4 4
>>> forM [0..7] (bufferReadWord8IO b2)
[4,5,6,7,0,1,2,3]

Finalizers

addFinalizer :: MonadIO m => Buffer mut pin Finalized heap -> IO () -> m () Source #

Add a finalizer.

The latest added finalizers are executed first. Finalizers are not guaranteed to run (e.g. if the program exits before the buffer is collected).

makeFinalizable :: MonadIO m => Buffer mut pin f heap -> m (Buffer mut pin Finalized heap) Source #

Make a buffer finalizable

The new buffer liveness is used to trigger finalizers.

touchBuffer :: MonadIO m => Buffer mut pin fin heap -> m () Source #

Touch a buffer

touch :: MonadIO m => a -> m () Source #

Touch a data

Conversions

bufferToListIO :: MonadIO m => Buffer mut pin fin heap -> m [Word8] Source #

Get contents as a list of bytes

class BufferToList a where Source #

Methods

bufferToList :: a -> [Word8] Source #

Get contents as a list of bytes

Instances
BufferToList BufferPF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferToList BufferF Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferToList BufferP Source # 
Instance details

Defined in Haskus.Memory.Buffer

BufferToList BufferI Source # 
Instance details

Defined in Haskus.Memory.Buffer