Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides support for working directly with Cap'N Proto messages.
Synopsis
- hPutMsg :: Handle -> ConstMsg -> IO ()
- hGetMsg :: Handle -> Int -> IO ConstMsg
- putMsg :: ConstMsg -> IO ()
- getMsg :: Int -> IO ConstMsg
- maxSegmentSize :: Int
- maxSegments :: Int
- encode :: MonadThrow m => ConstMsg -> m Builder
- decode :: MonadThrow m => ByteString -> m ConstMsg
- class Monad m => Message m msg where
- data Segment msg
- empty :: ConstMsg
- data ConstMsg
- getSegment :: (MonadThrow m, Message m msg) => msg -> Int -> m (Segment msg)
- getWord :: (MonadThrow m, Message m msg) => msg -> WordAddr -> m Word64
- data MutMsg s
- newMessage :: WriteCtx m s => m (MutMsg s)
- alloc :: WriteCtx m s => MutMsg s -> WordCount -> m WordAddr
- allocInSeg :: WriteCtx m s => MutMsg s -> Int -> WordCount -> m WordAddr
- newSegment :: WriteCtx m s => MutMsg s -> Int -> m (Int, Segment (MutMsg s))
- setWord :: (WriteCtx m s, MonadThrow m) => MutMsg s -> WordAddr -> Word64 -> m ()
- setSegment :: (WriteCtx m s, MonadThrow m) => MutMsg s -> Int -> Segment (MutMsg s) -> m ()
- type WriteCtx m s = (PrimMonad m, s ~ PrimState m, MonadThrow m)
Reading and writing messages
hGetMsg :: Handle -> Int -> IO ConstMsg Source #
reads a message from hGetMsg
handle limithandle
that is at most
limit
64-bit words in length.
Limits on message size
maxSegmentSize :: Int Source #
The maximum size of a segment supported by this libarary, in words.
maxSegments :: Int Source #
The maximum number of segments allowed in a message by this library.
Converting between messages and ByteString
s
encode :: MonadThrow m => ConstMsg -> m Builder Source #
encode
encodes a message as a bytestring builder.
decode :: MonadThrow m => ByteString -> m ConstMsg Source #
decode
decodes a message from a bytestring.
The segments will not be copied; the resulting message will be a view into the original bytestring. Runs in O(number of segments in the message).
Message type class
class Monad m => Message m msg where Source #
A Message
is a (possibly read-only) capnproto message. It is
parameterized over a monad in which operations are performed.
numSegs :: msg -> m Int Source #
numSegs
gets the number of segments in a message.
internalGetSeg :: msg -> Int -> m (Segment msg) Source #
gets the segment at index internalGetSeg
message indexindex
in message
. Most callers should use the getSegment
wrapper, instead
of calling this directly.
numWords :: Segment msg -> m Int Source #
Get the length of the segment, in units of 64-bit words.
slice :: Int -> Int -> Segment msg -> m (Segment msg) Source #
extracts a sub-section of the segment,
starting at index slice
start length segmentstart
, of length length
.
read :: Segment msg -> Int -> m Word64 Source #
reads a 64-bit word from the segement at the
given index. Consider using read
segment indexgetWord
on the message, instead of
calling this directly.
fromByteString :: ByteString -> m (Segment msg) Source #
Convert a ByteString to a segment.
toByteString :: Segment msg -> m ByteString Source #
Convert a segment to a byte string.
Instances
Monad m => Message m ConstMsg Source # | |
Defined in Data.Capnp.Message numSegs :: ConstMsg -> m Int Source # internalGetSeg :: ConstMsg -> Int -> m (Segment ConstMsg) Source # numWords :: Segment ConstMsg -> m Int Source # slice :: Int -> Int -> Segment ConstMsg -> m (Segment ConstMsg) Source # read :: Segment ConstMsg -> Int -> m Word64 Source # fromByteString :: ByteString -> m (Segment ConstMsg) Source # toByteString :: Segment ConstMsg -> m ByteString Source # | |
(PrimMonad m, s ~ PrimState m) => Message m (MutMsg s) Source # | |
Defined in Data.Capnp.Message numSegs :: MutMsg s -> m Int Source # internalGetSeg :: MutMsg s -> Int -> m (Segment (MutMsg s)) Source # numWords :: Segment (MutMsg s) -> m Int Source # slice :: Int -> Int -> Segment (MutMsg s) -> m (Segment (MutMsg s)) Source # read :: Segment (MutMsg s) -> Int -> m Word64 Source # fromByteString :: ByteString -> m (Segment (MutMsg s)) Source # toByteString :: Segment (MutMsg s) -> m ByteString Source # |
Immutable messages
empty
is an empty message, i.e. a minimal message with a null pointer as
its root object.
A read-only capnproto message.
ConstMsg
is an instance of the generic Message
type class. its
implementations of toByteString
and fromByteString
are O(1);
the underlying bytes are not copied.
Instances
Reading data from messages
getSegment :: (MonadThrow m, Message m msg) => msg -> Int -> m (Segment msg) Source #
fetches the given segment in the message.
It throws a getSegment
message indexBoundsError
if the address is out of bounds.
getWord :: (MonadThrow m, Message m msg) => msg -> WordAddr -> m Word64 Source #
returns the word at getWord
msg addraddr
within msg
. It throws a
BoundsError
if the address is out of bounds.
Mutable Messages
A MutMsg
is a mutable capnproto message. The type parameter s
is the
state token for the instance of PrimMonad
in which the message may be
modified.
Due to mutabilty, the implementations of toByteString
and fromByteString
must make full copies, and so are O(n) in the length of the segment.
Instances
newMessage :: WriteCtx m s => m (MutMsg s) Source #
Allocate a new empty message.
Allocating space in messages
alloc :: WriteCtx m s => MutMsg s -> WordCount -> m WordAddr Source #
allocates alloc
sizesize
words within a message. it returns the
starting address of the allocated memory.
allocInSeg :: WriteCtx m s => MutMsg s -> Int -> WordCount -> m WordAddr Source #
Like alloc
, but the second argument allows the caller to specify the
index of the segment in which to allocate the data.
newSegment :: WriteCtx m s => MutMsg s -> Int -> m (Int, Segment (MutMsg s)) Source #
allocates a new, initially empty segment in
newSegment
msg sizeHintmsg
with a capacity of sizeHint
. It returns the a pair of the segment
number and the segment itself. Amortized O(1).
Modifying messages
setWord :: (WriteCtx m s, MonadThrow m) => MutMsg s -> WordAddr -> Word64 -> m () Source #
sets the word at setWord
message address valueaddress
in the
message to value
. If the address is not valid in the message, a
BoundsError
will be thrown.
setSegment :: (WriteCtx m s, MonadThrow m) => MutMsg s -> Int -> Segment (MutMsg s) -> m () Source #
sets the segment at the given index
in the message. It throws a setSegment
message index segmentBoundsError
if the address is out of bounds.