| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Capnp
Contents
- Working with capnproto lists
- Working with capnproto Text and Data values.
- Working with messages
- Manipulating the root object of a message
- Marshalling data into and out of messages
- IO
- Type aliases for common contexts
- Converting between messages, Cap'N Proto values, and raw bytes
- Managing resource limits
- Freezing and thawing values
- Building messages in pure code
- Re-exported from Data.Default, for convienence.
Description
This module re-exports the most commonly used functionality from other modules in the library.
Users getting acquainted with the library are *strongly* encouraged to read the Capnp.Tutorial module before anything else.
Synopsis
- class ListElem msg e where
- class ListElem (MutMsg s) e => MutListElem s e where
- data Data msg
- dataBytes :: ReadCtx m msg => Data msg -> m ByteString
- data Text msg
- textBytes :: ReadCtx m msg => Text msg -> m ByteString
- data ConstMsg
- class Monad m => Message m msg where
- data Segment msg
- numSegs :: msg -> m Int
- numWords :: Segment msg -> m WordCount
- numCaps :: msg -> m Int
- internalGetSeg :: msg -> Int -> m (Segment msg)
- internalGetCap :: msg -> Int -> m Client
- slice :: WordCount -> WordCount -> Segment msg -> m (Segment msg)
- read :: Segment msg -> WordCount -> m Word64
- fromByteString :: ByteString -> m (Segment msg)
- toByteString :: Segment msg -> m ByteString
- data MutMsg s
- newMessage :: WriteCtx m s => Maybe WordCount -> m (MutMsg s)
- getRoot :: (FromStruct msg a, ReadCtx m msg) => msg -> m a
- newRoot :: (ToStruct (MutMsg s) a, Allocate s a, WriteCtx m s) => MutMsg s -> m a
- setRoot :: (ToStruct (MutMsg s) a, WriteCtx m s) => a -> m ()
- class Decerialize a where
- class Decerialize a => Cerialize a where
- module Capnp.IO
- type WriteCtx m s = (PrimMonad m, s ~ PrimState m, MonadThrow m)
- type ReadCtx m msg = (Message m msg, MonadThrow m, MonadLimit m)
- type RWCtx m s = (ReadCtx m (MutMsg s), WriteCtx m s)
- module Capnp.Convert
- module Capnp.TraversalLimit
- module Data.Mutable
- data PureBuilder s a
- createPure :: (MonadThrow m, Thaw a) => WordCount -> (forall s. PureBuilder s (Mutable s a)) -> m a
- def :: Default a => a
Working with capnproto lists
class ListElem msg e where Source #
Types which may be stored as an element of a capnproto list.
Methods
listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg e) Source #
Convert an untyped list to a list of this type. May fail
with a SchemaViolationError if the list does not have the
correct representation.
TODO: this is basically just fromPtr; refactor so this is less redundant.
toUntypedList :: List msg e -> List msg Source #
length :: List msg e -> Int Source #
Get the length of a list.
index :: ReadCtx m msg => Int -> List msg e -> m e Source #
gets the index i listith element of a list.
Instances
class ListElem (MutMsg s) e => MutListElem s e where Source #
Types which may be stored as an element of a *mutable* capnproto list.
Methods
setIndex :: RWCtx m s => e -> Int -> List (MutMsg s) e -> m () Source #
sets the setIndex value i listith index in list to value
newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) e) Source #
allocates and returns a new list of length
newList msg sizesize inside msg.
Instances
Working with capnproto Text and Data values.
A blob of bytes (Data in capnproto's schema language). The argument
to the data constructor is a slice into the message, containing the raw
bytes.
dataBytes :: ReadCtx m msg => Data msg -> m ByteString Source #
Convert a Data to a ByteString.
A textual string (Text in capnproto's schema language). On the wire,
this is NUL-terminated. The encoding should be UTF-8, but the library
does not verify this; users of the library must do validation themselves, if
they care about this.
Rationale: validation would require doing an up-front pass over the data, which runs counter to the overall design of capnproto.
textBytes :: ReadCtx m msg => Text msg -> m ByteString Source #
Convert a Text to a ByteString, comprising the raw bytes of the text
(not counting the NUL terminator).
Working with messages
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
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.
Methods
numSegs :: msg -> m Int Source #
numSegs gets the number of segments in a message.
numWords :: Segment msg -> m WordCount Source #
numWords gets the number of words in a segment.
numCaps :: msg -> m Int Source #
numCaps gets the number of capabilities in a message's capability
table.
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.
internalGetCap :: msg -> 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 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 -> WordCount -> 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
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 => Maybe WordCount -> m (MutMsg s) Source #
allocates a new empty message, with a single segment
having capacity newMessage sizeHintsizeHint. If sizeHint is Nothing, defaults to a sensible
value.
Manipulating the root object of a message
getRoot :: (FromStruct msg a, ReadCtx m msg) => msg -> m a Source #
getRoot returns the root object of a message.
newRoot :: (ToStruct (MutMsg s) a, Allocate s a, WriteCtx m s) => MutMsg s -> m a Source #
newRoot allocates and returns a new value inside the message, setting
it as the root object of the message.
setRoot :: (ToStruct (MutMsg s) a, WriteCtx m s) => a -> m () Source #
setRoot sets its argument to be the root object in its message.
Marshalling data into and out of messages
class Decerialize a where Source #
Types which may be extracted from a message.
typically, instances of Decerialize will be the algebraic data types
defined in generated code for the high-level API.
Associated Types
A variation on a which is encoded in the message.
For the case of instances in generated high-level API code, this will be the low-level API analouge of the type.
Methods
decerialize :: ReadCtx m ConstMsg => Cerial ConstMsg a -> m a Source #
Extract the value from the message.
Instances
class Decerialize a => Cerialize a where Source #
Types which may be inserted into a message.
Minimal complete definition
Nothing
Methods
cerialize :: RWCtx m s => MutMsg s -> a -> m (Cerial (MutMsg s) a) Source #
Cerialize a value into the supplied message, returning the result.
cerialize :: (RWCtx m s, Marshal a, Allocate s (Cerial (MutMsg s) a)) => MutMsg s -> a -> m (Cerial (MutMsg s) a) Source #
Cerialize a value into the supplied message, returning the result.
Instances
IO
module Capnp.IO
Type aliases for common contexts
type WriteCtx m s = (PrimMonad m, s ~ PrimState m, MonadThrow m) Source #
WriteCtx is the context needed for most write operations.
type ReadCtx m msg = (Message m msg, MonadThrow m, MonadLimit m) Source #
Type (constraint) synonym for the constraints needed for most read operations.
Converting between messages, Cap'N Proto values, and raw bytes
module Capnp.Convert
Managing resource limits
module Capnp.TraversalLimit
Freezing and thawing values
module Data.Mutable
Building messages in pure code
data PureBuilder s a Source #
PureBuilder is a monad transformer stack with the instnaces needed
manipulate mutable messages. is morally equivalent
to PureBuilder s aLimitT (CatchT (ST s)) a
Instances
createPure :: (MonadThrow m, Thaw a) => WordCount -> (forall s. PureBuilder s (Mutable s a)) -> m a Source #
creates a capnproto value in pure code according
to createPure limit mm, then freezes it without copying. If m calls throwM then
createPure rethrows the exception in the specified monad.