Safe Haskell | None |
---|---|
Language | Haskell2010 |
- newtype Poke a = Poke {}
- data PokeException = PokeException {}
- pokeException :: Text -> Poke a
- newtype Peek a = Peek {}
- data PeekResult a = PeekResult !(Ptr Word8) !a
- data PeekException = PeekException {}
- peekException :: Text -> Peek a
- tooManyBytes :: Int -> Int -> String -> IO void
- data PokeState
- pokeStatePtr :: PokeState -> Ptr Word8
- data PeekState
- peekStateEndPtr :: PeekState -> Ptr Word8
- type Offset = Int
- unsafeEncodeWith :: Poke () -> Int -> ByteString
- decodeWith :: Peek a -> ByteString -> Either PeekException a
- decodeExWith :: Peek a -> ByteString -> a
- decodeExPortionWith :: Peek a -> ByteString -> (Offset, a)
- decodeIOWith :: Peek a -> ByteString -> IO a
- decodeIOPortionWith :: Peek a -> ByteString -> IO (Offset, a)
- decodeIOWithFromPtr :: Peek a -> Ptr Word8 -> Int -> IO a
- decodeIOPortionWithFromPtr :: Peek a -> Ptr Word8 -> Int -> IO (Offset, a)
- pokeStorable :: Storable a => a -> Poke ()
- peekStorable :: forall a. (Storable a, Typeable a) => Peek a
- peekStorableTy :: forall a. Storable a => String -> Peek a
- pokeFromForeignPtr :: ForeignPtr a -> Int -> Int -> Poke ()
- peekToPlainForeignPtr :: String -> Int -> Peek (ForeignPtr a)
- pokeFromPtr :: Ptr a -> Int -> Int -> Poke ()
- pokeFromByteArray :: ByteArray# -> Int -> Int -> Poke ()
- peekToByteArray :: String -> Int -> Peek ByteArray
- unsafeMakePokeState :: Ptr Word8 -> IO (Ptr Word8) -> IO PokeState
- unsafeMakePeekState :: Ptr Word8 -> IO (Ptr Word8) -> IO PeekState
- maybeAlignmentBufferSize :: Maybe Int
Core Types
Poke
actions are useful for building sequential serializers.
They are actions which write values to bytes into memory specified by
a Ptr
base. The Applicative
and Monad
instances make it easy to
write serializations, by keeping track of the Offset
of the current
byte. They allow you to chain Poke
action such that subsequent
Poke
s write into subsequent portions of the output.
Poke | |
|
data PokeException Source #
Exception thrown while running poke
. Note that other types of
exceptions could also be thrown. Invocations of fail
in the Poke
monad causes this exception to be thrown.
PokeException
s are not expected to occur in ordinary circumstances,
and usually indicate a programming error.
pokeException :: Text -> Poke a Source #
Throws a PokeException
. These should be avoided when possible,
they usually indicate a programming error.
Peek
actions are useful for building sequential deserializers.
They are actions which read from memory and construct values from it.
The Applicative
and Monad
instances make it easy to chain these
together to get more complicated deserializers. This machinery keeps
track of the current Ptr
and end-of-buffer Ptr
.
data PeekResult a Source #
PeekResult !(Ptr Word8) !a |
data PeekException Source #
Exception thrown while running peek
. Note that other types of
exceptions can also be thrown. Invocations of fail
in the Poke
monad causes this exception to be thrown.
PeekException
is thrown when the data being decoded is invalid.
peekException :: Text -> Peek a Source #
Throws a PeekException
.
tooManyBytes :: Int -> Int -> String -> IO void Source #
Throws a PeekException
about an attempt to read too many bytes.
Holds a pokeStatePtr
, which is passed in to each Poke
action.
If the package is built with the 'force-alignment' flag, this also
has a hidden Ptr
field, which is used as scratch space during
unaligned writes.
Encode ByteString
unsafeEncodeWith :: Poke () -> Int -> ByteString Source #
Given a Poke
and its length, uses it to fill a ByteString
This function is unsafe because the provided length must exactly
match the number of bytes used by the Poke
. It will throw
PokeException
errors when the buffer is under or overshot. However,
in the case of overshooting the buffer, memory corruption and
segfaults may occur.
Decode ByteString
decodeWith :: Peek a -> ByteString -> Either PeekException a Source #
Decodes a value from a ByteString
, potentially throwing
exceptions, and taking a Peek
to run. It is an exception to not
consume all input.
decodeExWith :: Peek a -> ByteString -> a Source #
Decodes a value from a ByteString
, potentially throwing
exceptions, and taking a Peek
to run. It is an exception to not
consume all input.
decodeExPortionWith :: Peek a -> ByteString -> (Offset, a) Source #
Similar to decodeExWith
, but it allows there to be more of the
buffer remaining. The Offset
of the buffer contents immediately
after the decoded value is returned.
decodeIOWith :: Peek a -> ByteString -> IO a Source #
Decodes a value from a ByteString
, potentially throwing
exceptions, and taking a Peek
to run. It is an exception to not
consume all input.
decodeIOPortionWith :: Peek a -> ByteString -> IO (Offset, a) Source #
Similar to decodeExPortionWith
, but runs in the IO
monad.
decodeIOWithFromPtr :: Peek a -> Ptr Word8 -> Int -> IO a Source #
Like decodeIOWith
, but using Ptr
and length instead of a
ByteString
.
decodeIOPortionWithFromPtr :: Peek a -> Ptr Word8 -> Int -> IO (Offset, a) Source #
Like decodeIOPortionWith
, but using Ptr
and length instead of a ByteString
.
Storable
pokeStorable :: Storable a => a -> Poke () Source #
ForeignPtr
pokeFromForeignPtr :: ForeignPtr a -> Int -> Int -> Poke () Source #
Copy a section of memory, based on a ForeignPtr
, to the output.
Note that this operation is unsafe, the offset and length parameters
are not checked.
peekToPlainForeignPtr :: String -> Int -> Peek (ForeignPtr a) Source #
Allocate a plain ForeignPtr (no finalizers), of the specified length and fill it with bytes from the input.
pokeFromPtr :: Ptr a -> Int -> Int -> Poke () Source #
Copy a section of memory, based on a Ptr
, to the output. Note
that this operation is unsafe, because the offset and length
parameters are not checked.
ByteArray
pokeFromByteArray :: ByteArray# -> Int -> Int -> Poke () Source #
Copy a section of memory, based on a ByteArray#
, to the output.
Note that this operation is unsafe, because the offset and length
parameters are not checked.
peekToByteArray :: String -> Int -> Peek ByteArray Source #
Allocate a ByteArray of the specified length and fill it with bytes from the input.
Creation of PokeState / PeekState
Make a PokeState
from a buffer pointer.
The first argument is a pointer to the memory to write to. The second
argument is an IO action which is invoked if the store-core package
was built with the force-alignment
flag. The action should yield a
pointer to scratch memory as large as maybeAlignmentBufferSize
.
Since 0.4.2
Make a PeekState
from a buffer pointer.
The first argument is a pointer to the memory to write to. The second
argument is an IO action which is invoked if the store-core package
was built with the force-alignment
flag. The action should yield a
pointer to scratch memory as large as maybeAlignmentBufferSize
.
Since 0.4.2