capnp-0.11.0.0: Cap'n Proto for Haskell
Safe HaskellNone
LanguageHaskell2010

Capnp.Message

Description

This module provides support for working directly with Cap'N Proto messages.

Synopsis

Documentation

data Message (mut :: Mutability) Source #

A Cap'n Proto message, parametrized over its mutability.

Instances

Instances details
Eq (Message mut) Source # 
Instance details

Defined in Capnp.Message

Methods

(==) :: Message mut -> Message mut -> Bool #

(/=) :: Message mut -> Message mut -> Bool #

Thaw (Message 'Const) Source # 
Instance details

Defined in Capnp.Message

Associated Types

type Mutable s (Message 'Const) Source #

type Mutable s (Message 'Const) Source # 
Instance details

Defined in Capnp.Message

type Mutable s (Message 'Const) = Message ('Mut s)

data Segment (mut :: Mutability) Source #

A segment in a Cap'n Proto message.

Instances

Instances details
Eq (Segment mut) Source # 
Instance details

Defined in Capnp.Message

Methods

(==) :: Segment mut -> Segment mut -> Bool #

(/=) :: Segment mut -> Segment mut -> Bool #

Thaw (Segment 'Const) Source # 
Instance details

Defined in Capnp.Message

Associated Types

type Mutable s (Segment 'Const) Source #

type Mutable s (Segment 'Const) Source # 
Instance details

Defined in Capnp.Message

type Mutable s (Segment 'Const) = Segment ('Mut s)

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 s denotes a value that can be mutated in the scope of the state token s.

Constructors

Const 
Mut Type 

Reading and writing messages

hPutMsg :: Handle -> Message 'Const -> IO () Source #

hPutMsg handle msg writes msg to handle. If there is an exception, it will be an IOError raised by the underlying IO libraries.

hGetMsg :: Handle -> WordCount -> IO (Message 'Const) Source #

hGetMsg handle limit reads a message from handle that is at most limit 64-bit words in length.

putMsg :: Message 'Const -> IO () Source #

Equivalent to hPutMsg stdout

readMessage :: (MonadThrow m, MonadLimit m) => m Word32 -> (WordCount -> m (Segment 'Const)) -> m (Message 'Const) Source #

readMessage read32 readSegment 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 readSegment 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 writeSegment writes out the message. write32 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.

maxCaps :: Int Source #

The maximum number of capabilities allowed in a message by this library.

Converting between messages and ByteStrings

encode :: Message 'Const -> Builder Source #

encode encodes a message as a bytestring builder.

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.

singleSegment :: Segment 'Const -> Message 'Const Source #

Create a message from a single segment.

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 #

internalGetSeg message index gets the segment at index index in message. Most callers should use the getSegment wrapper, instead of calling this directly.

internalGetCap :: Message mut -> Int -> m Client Source #

internalGetCap cap index reads a capability from the message's capability table, returning the client. does not check bounds. Callers should use getCap instead.

slice :: WordCount -> WordCount -> Segment mut -> m (Segment mut) Source #

slice start length segment extracts a sub-section of the segment, starting at index start, of length length.

read :: Segment mut -> WordCount -> m Word64 Source #

read segment index reads a 64-bit word from the segement at the given index. Consider using getWord on the message, instead of calling this directly.

Instances

Instances details
Monad m => MonadReadMessage 'Const m Source # 
Instance details

Defined in Capnp.Message

(PrimMonad m, s ~ PrimState m) => MonadReadMessage ('Mut s) m Source # 
Instance details

Defined in Capnp.Message

getSegment :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> Int -> m (Segment mut) Source #

getSegment message index fetches the given segment in the message. It throws a BoundsError if the address is out of bounds.

getWord :: (MonadThrow m, MonadReadMessage mut m) => Message mut -> WordAddr -> m Word64 Source #

getWord msg addr returns the word at addr 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 #

getCap message index gets the capability with the given index from the message. throws BoundsError 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 #

newMessage sizeHint allocates a new empty message, with a single segment having capacity sizeHint. If sizeHint is Nothing, defaults to a sensible value.

Allocating space in messages

data WordPtr mut Source #

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.

Constructors

WordPtr 

Fields

Instances

Instances details
TraverseMsg WordPtr Source # 
Instance details

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 # 
Instance details

Defined in Capnp.Untyped

Methods

message :: WordPtr mut -> Message mut Source #

alloc :: WriteCtx m s => Message ('Mut s) -> WordCount -> m (WordPtr ('Mut s)) Source #

alloc size allocates size 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 #

Like alloc, but the second argument allows the caller to specify the index of the segment in which to allocate the data. Returns Nothing if there is insufficient space in that segment..

newSegment :: WriteCtx m s => Message ('Mut s) -> WordCount -> m (Int, Segment ('Mut s)) Source #

newSegment msg sizeHint allocates a new, initially empty segment in msg 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 sets the segment at the given index in the message. It throws a BoundsError if the address is out of bounds.

setWord :: WriteCtx m s => Message ('Mut s) -> WordAddr -> Word64 -> m () Source #

setWord message address value sets the word at address in the message to value. If the address is not valid in the message, a BoundsError will be thrown.

write :: WriteCtx m s => Segment ('Mut s) -> WordCount -> Word64 -> m () Source #

write segment index value writes a value to the 64-bit word at the provided index. Consider using setWord on the message, instead of calling this directly.

setCap :: WriteCtx m s => Message ('Mut s) -> Int -> Client -> m () Source #

setCap message index cap sets the sets the capability at index 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.

data Client Source #

Instances

Instances details
Eq Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Methods

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

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

Show Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

IsClient Client Source # 
Instance details

Defined in Capnp.Rpc.Untyped

Parse Capability Client Source # 
Instance details

Defined in Capnp.New.Basics

Methods

parse :: ReadCtx m 'Const => Raw 'Const Capability -> m Client Source #

encode :: RWCtx m s => Message ('Mut s) -> Client -> m (Raw ('Mut s) Capability) Source #

withCapTable :: Vector Client -> Message 'Const -> Message 'Const Source #

withCapTable replaces the capability table in the message.