| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Capnp.Message
Description
This module provides support for working directly with Cap'N Proto messages.
Synopsis
- data family Message (mut :: Mutability)
- data family 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
- segToVecMut :: (PrimMonad m, PrimState m ~ s) => Segment ('Mut s) -> m (MVector s Word64)
- 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
- getSegment :: 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
 
- getCap :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> Int -> m Client
- getCapTable :: Message 'Const -> Vector Client
- getWord :: MonadReadMessage mut m => WordPtr mut -> m Word64
- totalNumWords :: MonadReadMessage mut m => Message mut -> m WordCount
- 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 ()
- 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 family Message (mut :: Mutability) Source #
A Cap'n Proto message, parametrized over its mutability.
Instances
| MaybeMutable Message Source # | |
| Defined in Capnp.Message Methods thaw :: (PrimMonad m, PrimState m ~ s) => Message 'Const -> m (Message ('Mut s)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Message ('Mut s) -> m (Message 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Message 'Const -> m (Message ('Mut s)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Message ('Mut s) -> m (Message 'Const) Source # | |
| Eq (Message 'Const) Source # | |
| Eq (Message ('Mut s)) Source # | |
| newtype Message 'Const Source # | |
| Defined in Capnp.Message | |
| newtype Message ('Mut s) Source # | |
| Defined in Capnp.Message | |
data family Segment (mut :: Mutability) Source #
A segment in a Cap'n Proto message.
Instances
| MaybeMutable Segment Source # | |
| Defined in Capnp.Message Methods thaw :: (PrimMonad m, PrimState m ~ s) => Segment 'Const -> m (Segment ('Mut s)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Segment ('Mut s) -> m (Segment 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Segment 'Const -> m (Segment ('Mut s)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Segment ('Mut s) -> m (Segment 'Const) Source # | |
| Eq (Segment 'Const) Source # | |
| Eq (Segment ('Mut s)) Source # | |
| newtype Segment 'Const Source # | |
| Defined in Capnp.Message | |
| newtype Segment ('Mut s) Source # | |
| Defined in Capnp.Message | |
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 Mut ss.
Reading and writing messages
hGetMsg :: Handle -> WordCount -> IO (Message 'Const) Source #
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 #
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 #
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)
Accessing underlying storage
segToVecMut :: (PrimMonad m, PrimState m ~ s) => Segment ('Mut s) -> m (MVector s Word64) Source #
Return the underlying storage of a mutable segment, as a vector.
Note that the elements of the vector will be stored in little-endian form, regardless of CPU endianness. This is a low level function that you should probably not use.
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.
getSegment :: Message mut -> Int -> m (Segment mut) Source #
getSegment message indexindex
 in message.
internalGetCap :: Message mut -> Int -> m Client Source #
internalGetCap cap index
slice :: WordCount -> WordCount -> Segment mut -> m (Segment mut) Source #
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 # getSegment :: 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 # getSegment :: 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 # | |
getCap :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> Int -> m Client Source #
getCap message indexBoundsError if the index is out
 of bounds.
getCapTable :: Message 'Const -> Vector Client Source #
getCapTable gets the capability table from a ConstMsg.
totalNumWords :: MonadReadMessage mut m => Message mut -> m WordCount Source #
Return the total number of words in the message, i.e. the sum of
 the results of numWords on all segments.
Mutable Messages
newMessage :: WriteCtx m s => Maybe WordCount -> m (Message ('Mut s)) Source #
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
| HasMessage WordPtr Source # | |
| Defined in Capnp.Untyped | |
| 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 # | |
alloc :: WriteCtx m s => Message ('Mut s) -> WordCount -> m (WordPtr ('Mut s)) Source #
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 #
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 #
setSegment message index segment
write :: WriteCtx m s => Segment ('Mut s) -> WordCount -> Word64 -> m () Source #
write segment index valuesetWord on the message,
 instead of calling this directly.
setCap :: WriteCtx m s => Message ('Mut s) -> Int -> Client -> m () Source #
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.
A reference to a capability, which may be live either in the current vat or elsewhere. Holding a client affords making method calls on a capability or modifying the local vat's reference count to it.
nullClient :: Client Source #
A null client. This is the only client value that can be represented statically. Throws exceptions in response to all method calls.
withCapTable :: Vector Client -> Message 'Const -> Message 'Const Source #
withCapTable