| Safe Haskell | None |
|---|---|
| Language | Haskell2010 |
Data.Capnp
Contents
Description
Users getting acquainted with the library are *strongly* encouraged to read the Data.Capnp.Tutorial module before anything else.
Synopsis
- class ListElem msg e where
- data List msg e
- 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
- class Mutable a where
- data MutMsg s
- newMessage :: WriteCtx m s => m (MutMsg s)
- decodeMessage :: MonadThrow m => ByteString -> m ConstMsg
- encodeMessage :: MonadThrow m => ConstMsg -> m Builder
- hPutMsg :: Handle -> ConstMsg -> IO ()
- putMsg :: ConstMsg -> IO ()
- hGetMsg :: Handle -> Int -> IO ConstMsg
- getMsg :: Int -> IO ConstMsg
- 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 ()
- hGetValue :: FromStruct ConstMsg a => Handle -> Int -> IO a
- getValue :: FromStruct ConstMsg a => Int -> IO a
- 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 Data.Capnp.TraversalLimit
Working with capnproto lists
class ListElem msg e where Source #
Types which may be stored as an element of a capnproto list.
Methods
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.
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 # | |
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 | |
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 => m (MutMsg s) Source #
Allocate a new empty message.
decodeMessage :: MonadThrow m => ByteString -> m ConstMsg Source #
Alias for decode
Reading and writing messages
hGetMsg :: Handle -> Int -> IO ConstMsg Source #
reads a message from hGetMsg handle limithandle that is at most
limit 64-bit words in length.
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.
Reading values
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.
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.
Managing resource limits
module Data.Capnp.TraversalLimit