| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Capnp.Message
Description
Synopsis
- class Monad m => Message m msg where
- data Segment msg
- newtype ConstMsg = ConstMsg (Vector (Segment ConstMsg))
- data MutMsg s = MutMsg {
- mutMsgSegs :: MutVar s (MVector s (Segment (MutMsg s)))
- mutMsgLen :: MutVar s Int
- type WriteCtx m s = (PrimMonad m, s ~ PrimState m, MonadThrow m)
- class Mutable a where
- getSegment :: (MonadThrow m, Message m msg) => msg -> Int -> m (Segment msg)
- getWord :: (MonadThrow m, Message m msg) => msg -> WordAddr -> m Word64
- setSegment :: (WriteCtx m s, MonadThrow m) => MutMsg s -> Int -> Segment (MutMsg s) -> m ()
- setWord :: (WriteCtx m s, MonadThrow m) => MutMsg s -> WordAddr -> Word64 -> m ()
- encode :: MonadThrow m => ConstMsg -> m Builder
- decode :: MonadThrow m => ByteString -> m ConstMsg
- alloc :: WriteCtx m s => MutMsg s -> WordCount -> m WordAddr
- allocInSeg :: WriteCtx m s => MutMsg s -> Int -> WordCount -> m WordAddr
- newMessage :: WriteCtx m s => m (MutMsg s)
- newSegment :: WriteCtx m s => MutMsg s -> Int -> m (Int, Segment (MutMsg s))
- empty :: ConstMsg
- maxSegmentSize :: Int
- maxSegments :: Int
- hPutMsg :: Handle -> ConstMsg -> IO ()
- hGetMsg :: Handle -> Int -> IO ConstMsg
- putMsg :: ConstMsg -> IO ()
- getMsg :: Int -> IO ConstMsg
Documentation
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.
Minimal complete definition
numSegs, internalGetSeg, numWords, slice, read, fromByteString, toByteString
Methods
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
| MonadThrow m => Message m ConstMsg Source # | |
Defined in Data.Capnp.Message Methods 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 # | |
| WriteCtx m s => Message m (MutMsg s) Source # | |
Defined in Data.Capnp.Message Methods 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 # | |
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
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.
Constructors
| MutMsg | |
Fields
| |
Instances
type WriteCtx m s = (PrimMonad m, s ~ PrimState m, MonadThrow m) Source #
WriteCtx is the context needed for most write operations.
class Mutable a where Source #
The Mutable type class relates mutable and immutable versions of a type.
The instance is defined on the mutable variant; is the immutable
version of a mutable type Frozen aa.
Associated Types
The state token for a mutable value.
The immutable version of a.
Methods
thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope a) => Frozen a -> m a Source #
Convert an immutable value to a mutable one.
freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope a) => a -> m (Frozen a) Source #
Convert a mutable value to an immutable one.
Instances
| Mutable (MutMsg s) Source # | |
Defined in Data.Capnp.Message | |
| Mutable (Segment (MutMsg s)) Source # | |
| Mutable msg => Mutable (Struct msg) Source # | |
Defined in Data.Capnp.Untyped | |
| Mutable msg => Mutable (List msg) Source # | |
Defined in Data.Capnp.Untyped | |
| Mutable msg => Mutable (Ptr msg) Source # | |
Defined in Data.Capnp.Untyped | |
| Mutable msg => Mutable (ListOf msg (Maybe (Ptr msg))) Source # | |
Defined in Data.Capnp.Untyped Methods thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Maybe (Ptr msg)))) => Frozen (ListOf msg (Maybe (Ptr msg))) -> m (ListOf msg (Maybe (Ptr msg))) Source # freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Maybe (Ptr msg)))) => ListOf msg (Maybe (Ptr msg)) -> m (Frozen (ListOf msg (Maybe (Ptr msg)))) Source # | |
| Mutable msg => Mutable (ListOf msg (Struct msg)) Source # | |
Defined in Data.Capnp.Untyped Methods thaw :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Struct msg))) => Frozen (ListOf msg (Struct msg)) -> m (ListOf msg (Struct msg)) Source # freeze :: (MonadThrow m, PrimMonad m, PrimState m ~ Scope (ListOf msg (Struct msg))) => ListOf msg (Struct msg) -> m (Frozen (ListOf msg (Struct msg))) Source # | |
| Mutable msg => Mutable (ListOf msg Word64) Source # | |
| Mutable msg => Mutable (ListOf msg Word32) Source # | |
| Mutable msg => Mutable (ListOf msg Word16) Source # | |
| Mutable msg => Mutable (ListOf msg Word8) Source # | |
| Mutable msg => Mutable (ListOf msg Bool) Source # | |
| Mutable msg => Mutable (ListOf msg ()) Source # | |
Defined in Data.Capnp.Untyped | |
getSegment :: (MonadThrow m, Message m msg) => msg -> Int -> m (Segment msg) Source #
fetches the given segment in the message.
It throws a getSegment message indexBoundsError if the address is out of bounds.
getWord :: (MonadThrow m, Message m msg) => msg -> WordAddr -> m Word64 Source #
returns the word at getWord msg addraddr within msg. It throws a
BoundsError if the address is out of bounds.
setSegment :: (WriteCtx m s, MonadThrow m) => MutMsg s -> Int -> Segment (MutMsg 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, MonadThrow m) => MutMsg 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.
encode :: MonadThrow m => ConstMsg -> m Builder Source #
encode encodes a message as a bytestring builder.
decode :: MonadThrow m => ByteString -> m ConstMsg 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).
alloc :: WriteCtx m s => MutMsg s -> WordCount -> m WordAddr Source #
allocates alloc sizesize words within a message. it returns the
starting address of the allocated memory.
allocInSeg :: WriteCtx m s => MutMsg s -> Int -> WordCount -> m WordAddr Source #
Like alloc, but the second argument allows the caller to specify the
index of the segment in which to allocate the data.
newMessage :: WriteCtx m s => m (MutMsg s) Source #
Allocate a new empty message.
newSegment :: WriteCtx m s => MutMsg s -> Int -> m (Int, Segment (MutMsg s)) Source #
allocates a new, initially empty segment in
newSegment msg sizeHintmsg with a capacity of sizeHint. It returns the a pair of the segment
number and the segment itself. Amortized O(1).
empty is an empty message, i.e. a minimal message with a null pointer as
its root object.
maxSegmentSize :: Int 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.