| Safe Haskell | None | 
|---|---|
| Language | Haskell2010 | 
Capnp.Message
Description
This module provides support for working directly with Cap'N Proto messages.
Synopsis
- data Message (mut :: Mutability)
 - data Segment (mut :: Mutability)
 - data Mutability
 - hPutMsg :: Handle -> Message 'Const -> IO ()
 - hGetMsg :: Handle -> WordCount -> IO (Message 'Const)
 - putMsg :: Message 'Const -> IO ()
 - getMsg :: WordCount -> IO (Message 'Const)
 - readMessage :: (MonadThrow m, MonadLimit m) => m Word32 -> (WordCount -> m (Segment 'Const)) -> m (Message 'Const)
 - writeMessage :: MonadThrow m => Message 'Const -> (Word32 -> m ()) -> (Segment 'Const -> m ()) -> m ()
 - maxSegmentSize :: WordCount
 - maxSegments :: Int
 - maxCaps :: Int
 - encode :: Message 'Const -> Builder
 - decode :: MonadThrow m => ByteString -> m (Message 'Const)
 - toByteString :: Segment 'Const -> ByteString
 - fromByteString :: ByteString -> Segment 'Const
 - empty :: Message 'Const
 - singleSegment :: Segment 'Const -> Message 'Const
 - class Monad m => MonadReadMessage mut m where
- numSegs :: Message mut -> m Int
 - numWords :: Segment mut -> m WordCount
 - numCaps :: Message mut -> m Int
 - internalGetSeg :: Message mut -> Int -> m (Segment mut)
 - internalGetCap :: Message mut -> Int -> m Client
 - slice :: WordCount -> WordCount -> Segment mut -> m (Segment mut)
 - read :: Segment mut -> WordCount -> m Word64
 
 - getSegment :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> Int -> m (Segment mut)
 - getWord :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> WordAddr -> m Word64
 - getCap :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> Int -> m Client
 - getCapTable :: Message 'Const -> Vector Client
 - newMessage :: WriteCtx m s => Maybe WordCount -> m (Message ('Mut s))
 - data WordPtr mut = WordPtr {}
 - alloc :: WriteCtx m s => Message ('Mut s) -> WordCount -> m (WordPtr ('Mut s))
 - allocInSeg :: WriteCtx m s => Message ('Mut s) -> Int -> WordCount -> m (Maybe (WordPtr ('Mut s)))
 - newSegment :: WriteCtx m s => Message ('Mut s) -> WordCount -> m (Int, Segment ('Mut s))
 - setSegment :: WriteCtx m s => Message ('Mut s) -> Int -> Segment ('Mut s) -> m ()
 - setWord :: WriteCtx m s => Message ('Mut s) -> WordAddr -> Word64 -> m ()
 - write :: WriteCtx m s => Segment ('Mut s) -> WordCount -> Word64 -> m ()
 - setCap :: WriteCtx m s => Message ('Mut s) -> Int -> Client -> m ()
 - appendCap :: WriteCtx m s => Message ('Mut s) -> Client -> m Int
 - type WriteCtx m s = (PrimMonad m, s ~ PrimState m, MonadThrow m)
 - data Client
 - nullClient :: Client
 - withCapTable :: Vector Client -> Message 'Const -> Message 'Const
 
Documentation
data Message (mut :: Mutability) Source #
A Cap'n Proto message, parametrized over its mutability.
Instances
| Eq (Message mut) Source # | |
| Thaw (Message 'Const) Source # | |
Defined in Capnp.Message Methods thaw :: (PrimMonad m, PrimState m ~ s) => Message 'Const -> m (Mutable s (Message 'Const)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Message 'Const) -> m (Message 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Message 'Const -> m (Mutable s (Message 'Const)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Message 'Const) -> m (Message 'Const) Source #  | |
| type Mutable s (Message 'Const) Source # | |
data Segment (mut :: Mutability) Source #
A segment in a Cap'n Proto message.
Instances
| Eq (Segment mut) Source # | |
| Thaw (Segment 'Const) Source # | |
Defined in Capnp.Message Methods thaw :: (PrimMonad m, PrimState m ~ s) => Segment 'Const -> m (Mutable s (Segment 'Const)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Segment 'Const) -> m (Segment 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Segment 'Const -> m (Mutable s (Segment 'Const)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Segment 'Const) -> m (Segment 'Const) Source #  | |
| type Mutable s (Segment 'Const) Source # | |
data Mutability Source #
Mutability is used as a type parameter (with the DataKinds extension)
 to indicate the mutability of some values in this library; Const denotes
 an immutable value, while  denotes a value that can be mutated
 in the scope of the state token Mut ss.
Reading and writing messages
hGetMsg :: Handle -> WordCount -> IO (Message 'Const) Source #
 reads a message from hGetMsg handle limithandle that is at most
 limit 64-bit words in length.
readMessage :: (MonadThrow m, MonadLimit m) => m Word32 -> (WordCount -> m (Segment 'Const)) -> m (Message 'Const) Source #
 reads in a message using the
 monadic context, which should manage the current read position,
 into a message. read32 should read a 32-bit little-endian integer,
 and readMessage read32 readSegmentreadSegment n should read a blob of n 64-bit words.
 The size of the message (in 64-bit words) is deducted from the traversal,
 limit which can be used to set the maximum message size.
writeMessage :: MonadThrow m => Message 'Const -> (Word32 -> m ()) -> (Segment 'Const -> m ()) -> m () Source #
 writes out the message. writeMesage write32 writeSegmentwrite32
 should write a 32-bit word in little-endian format to the output stream.
 writeSegment should write a blob.
Limits on message size
maxSegmentSize :: WordCount 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 ByteStrings
decode :: MonadThrow m => ByteString -> m (Message 'Const) 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).
toByteString :: Segment 'Const -> ByteString Source #
Convert a segment to a byte string. O(1)
fromByteString :: ByteString -> Segment 'Const Source #
Convert a ByteString to a segment. O(1)
Immutable messages
empty :: Message 'Const Source #
empty is an empty message, i.e. a minimal message with a null pointer as
 its root object.
Reading data from messages
class Monad m => MonadReadMessage mut m where Source #
A Message is a (possibly read-only) capnproto message. It is
 parameterized over a monad in which operations are performed.
Methods
numSegs :: Message mut -> m Int Source #
numSegs gets the number of segments in a message.
numWords :: Segment mut -> m WordCount Source #
numWords gets the number of words in a segment.
numCaps :: Message mut -> m Int Source #
numCaps gets the number of capabilities in a message's capability
 table.
internalGetSeg :: Message mut -> Int -> m (Segment mut) Source #
 gets the segment at index internalGetSeg message indexindex
 in message. Most callers should use the getSegment wrapper, instead
 of calling this directly.
internalGetCap :: Message mut -> Int -> m Client Source #
 reads a capability from the message's
 capability table, returning the client. does not check bounds. Callers
 should use getCap instead.internalGetCap cap index
slice :: WordCount -> WordCount -> Segment mut -> m (Segment mut) Source #
 extracts a sub-section of the segment,
 starting at index slice start length segmentstart, of length length.
Instances
| Monad m => MonadReadMessage 'Const m Source # | |
Defined in Capnp.Message Methods numSegs :: Message 'Const -> m Int Source # numWords :: Segment 'Const -> m WordCount Source # numCaps :: Message 'Const -> m Int Source # internalGetSeg :: Message 'Const -> Int -> m (Segment 'Const) Source # internalGetCap :: Message 'Const -> Int -> m Client Source # slice :: WordCount -> WordCount -> Segment 'Const -> m (Segment 'Const) Source #  | |
| (PrimMonad m, s ~ PrimState m) => MonadReadMessage ('Mut s) m Source # | |
Defined in Capnp.Message Methods numSegs :: Message ('Mut s) -> m Int Source # numWords :: Segment ('Mut s) -> m WordCount Source # numCaps :: Message ('Mut s) -> m Int Source # internalGetSeg :: Message ('Mut s) -> Int -> m (Segment ('Mut s)) Source # internalGetCap :: Message ('Mut s) -> Int -> m Client Source # slice :: WordCount -> WordCount -> Segment ('Mut s) -> m (Segment ('Mut s)) Source #  | |
getSegment :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> Int -> m (Segment mut) Source #
 fetches the given segment in the message.
 It throws a getSegment message indexBoundsError if the address is out of bounds.
getWord :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> WordAddr -> m Word64 Source #
 returns the word at getWord msg addraddr within msg. It throws a
 BoundsError if the address is out of bounds.
getCap :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> Int -> m Client Source #
 gets the capability with the given index from
 the message. throws getCap message indexBoundsError if the index is out
 of bounds.
getCapTable :: Message 'Const -> Vector Client Source #
getCapTable gets the capability table from a ConstMsg.
Mutable Messages
newMessage :: WriteCtx m s => Maybe WordCount -> m (Message ('Mut s)) Source #
 allocates a new empty message, with a single segment
 having capacity newMessage sizeHintsizeHint. If sizeHint is Nothing, defaults to a sensible
 value.
Allocating space in messages
A pointer to a location in a message. This encodes the same
 information as a WordAddr, but also includes direct references
 to the segment and message, which can improve performance in very
 low-level code.
Instances
| TraverseMsg WordPtr Source # | |
Defined in Capnp.Untyped Methods tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> WordPtr mutA -> m (WordPtr mutB) Source #  | |
| HasMessage (WordPtr mut) mut Source # | |
alloc :: WriteCtx m s => Message ('Mut s) -> WordCount -> m (WordPtr ('Mut s)) Source #
 allocates alloc sizesize words within a message. it returns the
 starting address of the allocated memory, as well as a direct reference
 to the segment. The latter is redundant information, but this is used
 in low-level code where this can improve performance.
allocInSeg :: WriteCtx m s => Message ('Mut s) -> Int -> WordCount -> m (Maybe (WordPtr ('Mut s))) Source #
newSegment :: WriteCtx m s => Message ('Mut s) -> WordCount -> m (Int, Segment ('Mut s)) Source #
 allocates a new, initially empty segment in
 newSegment msg sizeHintmsg with a capacity of sizeHint words. It returns the a pair of the
 segment number and the segment itself. Amortized O(1).
Modifying messages
setSegment :: WriteCtx m s => Message ('Mut s) -> Int -> Segment ('Mut 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.
setWord :: WriteCtx m s => Message ('Mut 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.
setCap :: WriteCtx m s => Message ('Mut s) -> Int -> Client -> m () Source #
 sets the sets the capability at setCap message index capindex in
 the message's capability table to cap. If the index is out of bounds, a
 BoundsError will be thrown.
appendCap :: WriteCtx m s => Message ('Mut s) -> Client -> m Int Source #
appendCap appends a new capabilty to the end of a message's capability
 table, returning its index.
type WriteCtx m s = (PrimMonad m, s ~ PrimState m, MonadThrow m) Source #
WriteCtx is the context needed for most write operations.
nullClient :: Client Source #
withCapTable :: Vector Client -> Message 'Const -> Message 'Const Source #
 replaces the capability table in the message.withCapTable