Safe Haskell | None |
---|---|
Language | Haskell2010 |
The types and functions in this module know about things like structs and lists, but are not schema aware.
Each of the data types exported by this module is parametrized over a Message type (see Capnp.Message), used as the underlying storage.
Synopsis
- data Ptr msg
- data List msg
- data Struct msg
- data ListOf msg a
- data Cap msg
- structByteCount :: Struct msg -> ByteCount
- structWordCount :: Struct msg -> WordCount
- structPtrCount :: Struct msg -> Word16
- structListByteCount :: ListOf msg (Struct msg) -> ByteCount
- structListWordCount :: ListOf msg (Struct msg) -> WordCount
- structListPtrCount :: ListOf msg (Struct msg) -> Word16
- getData :: ReadCtx m msg => Int -> Struct msg -> m Word64
- getPtr :: ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg))
- setData :: (ReadCtx m (MutMsg s), WriteCtx m s) => Word64 -> Int -> Struct (MutMsg s) -> m ()
- setPtr :: (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m ()
- copyStruct :: RWCtx m s => Struct (MutMsg s) -> Struct (MutMsg s) -> m ()
- getClient :: ReadCtx m msg => Cap msg -> m Client
- get :: ReadCtx m msg => msg -> WordAddr -> m (Maybe (Ptr msg))
- index :: ReadCtx m msg => Int -> ListOf msg a -> m a
- length :: ListOf msg a -> Int
- setIndex :: RWCtx m s => a -> Int -> ListOf (MutMsg s) a -> m ()
- take :: MonadThrow m => Int -> ListOf msg a -> m (ListOf msg a)
- rootPtr :: ReadCtx m msg => msg -> m (Struct msg)
- setRoot :: WriteCtx m s => Struct (MutMsg s) -> m ()
- rawBytes :: ReadCtx m msg => ListOf msg Word8 -> m ByteString
- type ReadCtx m msg = (Message m msg, MonadThrow m, MonadLimit m)
- type RWCtx m s = (ReadCtx m (MutMsg s), WriteCtx m s)
- class HasMessage a where
- class HasMessage a => MessageDefault a where
- messageDefault :: InMessage a -> a
- allocStruct :: WriteCtx m s => MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s))
- allocCompositeList :: WriteCtx m s => MutMsg s -> Word16 -> Word16 -> Int -> m (ListOf (MutMsg s) (Struct (MutMsg s)))
- allocList0 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) ())
- allocList1 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Bool)
- allocList8 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word8)
- allocList16 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word16)
- allocList32 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word32)
- allocList64 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word64)
- allocListPtr :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) (Maybe (Ptr (MutMsg s))))
- appendCap :: WriteCtx m s => MutMsg s -> Client -> m (Cap (MutMsg s))
- class TraverseMsg f where
- tMsg :: Applicative m => (msgA -> m msgB) -> f msgA -> m (f msgB)
Documentation
A an absolute pointer to a value (of arbitrary type) in a message. Note that there is no variant for far pointers, which don't make sense with absolute addressing.
Instances
A list of values (of arbitrary type) in a message.
List0 (ListOf msg ()) | |
List1 (ListOf msg Bool) | |
List8 (ListOf msg Word8) | |
List16 (ListOf msg Word16) | |
List32 (ListOf msg Word32) | |
List64 (ListOf msg Word64) | |
ListPtr (ListOf msg (Maybe (Ptr msg))) | |
ListStruct (ListOf msg (Struct msg)) |
Instances
TraverseMsg List Source # | |
Defined in Capnp.Untyped | |
Thaw msg => Thaw (List msg) Source # | |
Defined in Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => List msg -> m (Mutable s (List msg)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List msg) -> m (List msg) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => List msg -> m (Mutable s (List msg)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List msg) -> m (List msg) Source # | |
HasMessage (List msg) Source # | |
type Mutable s (List msg) Source # | |
Defined in Capnp.Untyped | |
type InMessage (List msg) Source # | |
Defined in Capnp.Untyped |
A struct value in a message.
Instances
A list of values of type a
in a message.
Instances
A Capability in a message.
structByteCount :: Struct msg -> ByteCount Source #
Get the size (in bytes) of a struct's data section.
structWordCount :: Struct msg -> WordCount Source #
Get the size (in words) of a struct's data section.
structPtrCount :: Struct msg -> Word16 Source #
Get the size of a struct's pointer section.
structListByteCount :: ListOf msg (Struct msg) -> ByteCount Source #
Get the size (in words) of the data sections in a struct list.
structListWordCount :: ListOf msg (Struct msg) -> WordCount Source #
Get the size (in words) of the data sections in a struct list.
structListPtrCount :: ListOf msg (Struct msg) -> Word16 Source #
Get the size of the pointer sections in a struct list.
getData :: ReadCtx m msg => Int -> Struct msg -> m Word64 Source #
gets the getData
i structi
th word from the struct's data section,
returning 0 if it is absent.
getPtr :: ReadCtx m msg => Int -> Struct msg -> m (Maybe (Ptr msg)) Source #
gets the getPtr
i structi
th word from the struct's pointer section,
returning Nothing if it is absent.
setData :: (ReadCtx m (MutMsg s), WriteCtx m s) => Word64 -> Int -> Struct (MutMsg s) -> m () Source #
sets the setData
value i structi
th word in the struct's data section
to value
.
setPtr :: (ReadCtx m (MutMsg s), WriteCtx m s) => Maybe (Ptr (MutMsg s)) -> Int -> Struct (MutMsg s) -> m () Source #
sets the setData
value i structi
th pointer in the struct's pointer
section to value
.
copyStruct :: RWCtx m s => Struct (MutMsg s) -> Struct (MutMsg s) -> m () Source #
copies the source struct to the destination struct.copyStruct
dest src
get :: ReadCtx m msg => msg -> WordAddr -> m (Maybe (Ptr msg)) Source #
get msg addr
returns the Ptr stored at addr
in msg
.
Deducts 1 from the quota for each word read (which may be multiple in the
case of far pointers).
index :: ReadCtx m msg => Int -> ListOf msg a -> m a Source #
index i list
returns the ith element in list
. Deducts 1 from the quota
setIndex :: RWCtx m s => a -> Int -> ListOf (MutMsg s) a -> m () Source #
'setIndex value i list
Set the i
th element of list
to value
.
take :: MonadThrow m => Int -> ListOf msg a -> m (ListOf msg a) Source #
Return a prefix of the list, of the given length.
setRoot :: WriteCtx m s => Struct (MutMsg s) -> m () Source #
Make the given struct the root object of its message.
rawBytes :: ReadCtx m msg => ListOf msg Word8 -> m ByteString Source #
rawBytes
returns the raw bytes corresponding to the list.
type ReadCtx m msg = (Message m msg, MonadThrow m, MonadLimit m) Source #
Type (constraint) synonym for the constraints needed for most read operations.
class HasMessage a where Source #
Types a
whose storage is owned by a message..
Instances
class HasMessage a => MessageDefault a where Source #
Types which have a "default" value, but require a message to construct it.
The default is usually conceptually zero-size. This is mostly useful for generated code, so that it can use standard decoding techniques on default values.
messageDefault :: InMessage a -> a Source #
Instances
allocStruct :: WriteCtx m s => MutMsg s -> Word16 -> Word16 -> m (Struct (MutMsg s)) Source #
Allocate a struct in the message.
:: WriteCtx m s | |
=> MutMsg s | The message to allocate in. |
-> Word16 | The size of the data section |
-> Word16 | The size of the pointer section |
-> Int | The length of the list in elements. |
-> m (ListOf (MutMsg s) (Struct (MutMsg s))) |
Allocate a composite list.
allocList0 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) ()) Source #
Allocate a list of capnproto Void
values.
allocList1 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Bool) Source #
Allocate a list of booleans
allocList8 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word8) Source #
Allocate a list of 8-bit values.
allocList16 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word16) Source #
Allocate a list of 16-bit values.
allocList32 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word32) Source #
Allocate a list of 32-bit values.
allocList64 :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) Word64) Source #
Allocate a list of 64-bit words.
allocListPtr :: WriteCtx m s => MutMsg s -> Int -> m (ListOf (MutMsg s) (Maybe (Ptr (MutMsg s)))) Source #
Allocate a list of pointers.
class TraverseMsg f where Source #
TraverseMsg
is basically Traversable
from the prelude, but
the intent is that rather than conceptually being a "container",
the instance is a value backed by a message, and the point of the
type class is to be able to apply transformations to the underlying
message.
We don't just use Traversable
for this because while algebraically
it makes sense, it would be very unintuitive to e.g. have the
Traversable
instance for List
not traverse over the *elements*
of the list.
tMsg :: Applicative m => (msgA -> m msgB) -> f msgA -> m (f msgB) Source #
Instances
TraverseMsg Struct Source # | |
Defined in Capnp.Untyped | |
TraverseMsg Cap Source # | |
Defined in Capnp.Untyped | |
TraverseMsg List Source # | |
Defined in Capnp.Untyped | |
TraverseMsg Ptr Source # | |
Defined in Capnp.Untyped |
Orphan instances
Thaw a => Thaw (Maybe a) Source # | |
thaw :: (PrimMonad m, PrimState m ~ s) => Maybe a -> m (Mutable s (Maybe a)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Maybe a) -> m (Maybe a) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Maybe a -> m (Mutable s (Maybe a)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (Maybe a) -> m (Maybe a) Source # |