Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module re-exports the most commonly used functionality from the high-level API. See also Data.Capnp, which does the same for the low-level API.
Users getting acquainted with the library are *strongly* encouraged to read the Data.Capnp.Tutorial module before anything else.
Synopsis
- hPutValue :: (Cerialize RealWorld a, ToStruct (MutMsg RealWorld) (Cerial (MutMsg RealWorld) a)) => Handle -> a -> IO ()
- hGetValue :: FromStruct ConstMsg a => Handle -> Int -> IO a
- putValue :: (Cerialize RealWorld a, ToStruct (MutMsg RealWorld) (Cerial (MutMsg RealWorld) a)) => a -> IO ()
- getValue :: FromStruct ConstMsg a => Int -> IO a
- decodeMessage :: MonadThrow m => ByteString -> m ConstMsg
- encodeMessage :: MonadThrow m => ConstMsg -> m Builder
- data ConstMsg
- class Monad m => Message m msg where
- data Segment msg
- getRoot :: (FromStruct msg a, ReadCtx m msg) => msg -> m a
- class Decerialize a where
- type Cerial msg a
- class Decerialize a => Cerialize s a where
- module Data.Capnp.TraversalLimit
- type Text = Text
- type Data = ByteString
- def :: Default a => a
Reading and writing values
hPutValue :: (Cerialize RealWorld a, ToStruct (MutMsg RealWorld) (Cerial (MutMsg RealWorld) a)) => Handle -> a -> IO () Source #
hGetValue :: FromStruct ConstMsg a => Handle -> Int -> IO a Source #
reads a message from hGetValue
limit handlehandle
, returning its root object.
limit
is used as both a cap on the size of a message which may be read and, for types
in the high-level API, the traversal limit when decoding the message.
It may throw a Error
if there is a problem decoding the message,
or an IOError
raised by the underlying IO libraries.
putValue :: (Cerialize RealWorld a, ToStruct (MutMsg RealWorld) (Cerial (MutMsg RealWorld) a)) => a -> IO () Source #
Working directly with messages
decodeMessage :: MonadThrow m => ByteString -> m ConstMsg Source #
Alias for decode
encodeMessage :: MonadThrow m => ConstMsg -> m Builder Source #
Alias for encode
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.
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 # |
Getting values in and out of messages
getRoot :: (FromStruct msg a, ReadCtx m msg) => msg -> m a Source #
getRoot
returns the root object of a message.
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.
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.
decerialize :: ReadCtx m ConstMsg => Cerial ConstMsg a -> m a Source #
Extract the value from the message.
Instances
class Decerialize a => Cerialize s a where Source #
Types which may be inserted into a message.
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
Managing resource limits
module Data.Capnp.TraversalLimit
Aliases for built-in capnproto types.
type Data = ByteString Source #
A capnproto Data
value. This is just an alias for ByteString
.