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 the mutability of the message it contains (see Capnp.Message).
Synopsis
- data Ptr mut
- data List mut
- data Struct mut
- data ListOf mut a
- data Cap mut
- 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 ('Mut s), WriteCtx m s) => Word64 -> Int -> Struct ('Mut s) -> m ()
- setPtr :: (ReadCtx m ('Mut s), WriteCtx m s) => Maybe (Ptr ('Mut s)) -> Int -> Struct ('Mut s) -> m ()
- copyStruct :: RWCtx m s => Struct ('Mut s) -> Struct ('Mut s) -> m ()
- copyPtr :: RWCtx m s => Message ('Mut s) -> Maybe (Ptr ('Mut s)) -> m (Maybe (Ptr ('Mut s)))
- copyList :: RWCtx m s => Message ('Mut s) -> List ('Mut s) -> m (List ('Mut s))
- copyCap :: RWCtx m s => Message ('Mut s) -> Cap ('Mut s) -> m (Cap ('Mut s))
- copyListOf :: RWCtx m s => ListOf ('Mut s) a -> ListOf ('Mut s) a -> m ()
- getClient :: ReadCtx m mut => Cap mut -> m Client
- get :: ReadCtx m mut => WordPtr mut -> m (Maybe (Ptr mut))
- index :: ReadCtx m mut => Int -> ListOf mut a -> m a
- length :: ListOf msg a -> Int
- setIndex :: RWCtx m s => a -> Int -> ListOf ('Mut s) a -> m ()
- take :: MonadThrow m => Int -> ListOf msg a -> m (ListOf msg a)
- rootPtr :: ReadCtx m mut => Message mut -> m (Struct mut)
- setRoot :: WriteCtx m s => Struct ('Mut s) -> m ()
- rawBytes :: ReadCtx m 'Const => ListOf 'Const Word8 -> m ByteString
- type ReadCtx m mut = (MonadReadMessage mut m, MonadThrow m, MonadLimit m)
- type RWCtx m s = (ReadCtx m ('Mut s), WriteCtx m s)
- class HasMessage a mut | a -> mut where
- class HasMessage a mut => MessageDefault a mut where
- messageDefault :: ReadCtx m mut => Message mut -> m a
- allocStruct :: WriteCtx m s => Message ('Mut s) -> Word16 -> Word16 -> m (Struct ('Mut s))
- allocCompositeList :: WriteCtx m s => Message ('Mut s) -> Word16 -> Word16 -> Int -> m (ListOf ('Mut s) (Struct ('Mut s)))
- allocList0 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) ())
- allocList1 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Bool)
- allocList8 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word8)
- allocList16 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word16)
- allocList32 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word32)
- allocList64 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word64)
- allocListPtr :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) (Maybe (Ptr ('Mut s))))
- appendCap :: WriteCtx m s => Message ('Mut s) -> Client -> m (Cap ('Mut s))
- class TraverseMsg f where
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 mut ()) | |
List1 (ListOf mut Bool) | |
List8 (ListOf mut Word8) | |
List16 (ListOf mut Word16) | |
List32 (ListOf mut Word32) | |
List64 (ListOf mut Word64) | |
ListPtr (ListOf mut (Maybe (Ptr mut))) | |
ListStruct (ListOf mut (Struct mut)) |
Instances
TraverseMsg List Source # | |
Defined in Capnp.Untyped tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> List mutA -> m (List mutB) Source # | |
Thaw (List 'Const) Source # | |
Defined in Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => List 'Const -> m (Mutable s (List 'Const)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List 'Const) -> m (List 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => List 'Const -> m (Mutable s (List 'Const)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Mutable s (List 'Const) -> m (List 'Const) Source # | |
HasMessage (List mut) mut Source # | |
type Mutable s (List 'Const) Source # | |
type ReprFor (List mut) Source # | |
A struct value in a message.
Instances
A list of values of type a
in a message.
Instances
A Capability in a message.
Instances
TraverseMsg Cap Source # | |
Defined in Capnp.Untyped tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Cap mutA -> m (Cap mutB) Source # | |
ToPtr s (Maybe (Cap ('Mut s))) Source # | |
FromPtr mut (Maybe (Cap mut)) Source # | |
HasMessage (Cap mut) mut Source # | |
type ReprFor (Cap mut) Source # | |
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 ('Mut s), WriteCtx m s) => Word64 -> Int -> Struct ('Mut s) -> m () Source #
sets the setData
value i structi
th word in the struct's data section
to value
.
setPtr :: (ReadCtx m ('Mut s), WriteCtx m s) => Maybe (Ptr ('Mut s)) -> Int -> Struct ('Mut s) -> m () Source #
sets the setData
value i structi
th pointer in the struct's pointer
section to value
.
copyStruct :: RWCtx m s => Struct ('Mut s) -> Struct ('Mut s) -> m () Source #
copies the source struct to the destination struct.copyStruct
dest src
copyPtr :: RWCtx m s => Message ('Mut s) -> Maybe (Ptr ('Mut s)) -> m (Maybe (Ptr ('Mut s))) Source #
Make a copy of the value at the pointer, in the target message.
copyList :: RWCtx m s => Message ('Mut s) -> List ('Mut s) -> m (List ('Mut s)) Source #
Make a copy of the list, in the target message.
copyCap :: RWCtx m s => Message ('Mut s) -> Cap ('Mut s) -> m (Cap ('Mut s)) Source #
Make a copy of a capability inside the target message.
copyListOf :: RWCtx m s => ListOf ('Mut s) a -> ListOf ('Mut s) a -> m () Source #
Make a copy of the list, in the target message.
getClient :: ReadCtx m mut => Cap mut -> m Client Source #
Extract a client (indepedent of the messsage) from the capability.
get :: ReadCtx m mut => WordPtr mut -> m (Maybe (Ptr mut)) Source #
get ptr
returns the Ptr stored at ptr
.
Deducts 1 from the quota for each word read (which may be multiple in the
case of far pointers).
index :: ReadCtx m mut => Int -> ListOf mut 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 ('Mut 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.
rootPtr :: ReadCtx m mut => Message mut -> m (Struct mut) Source #
Returns the root pointer of a message.
setRoot :: WriteCtx m s => Struct ('Mut s) -> m () Source #
Make the given struct the root object of its message.
rawBytes :: ReadCtx m 'Const => ListOf 'Const Word8 -> m ByteString Source #
rawBytes
returns the raw bytes corresponding to the list.
type ReadCtx m mut = (MonadReadMessage mut m, MonadThrow m, MonadLimit m) Source #
Type (constraint) synonym for the constraints needed for most read operations.
class HasMessage a mut | a -> mut where Source #
Types a
whose storage is owned by a message..
Instances
class HasMessage a mut => MessageDefault a mut 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 :: ReadCtx m mut => Message mut -> m a Source #
Instances
allocStruct :: WriteCtx m s => Message ('Mut s) -> Word16 -> Word16 -> m (Struct ('Mut s)) Source #
Allocate a struct in the message.
:: WriteCtx m s | |
=> Message ('Mut 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 ('Mut s) (Struct ('Mut s))) |
Allocate a composite list.
allocList0 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) ()) Source #
Allocate a list of capnproto Void
values.
allocList1 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Bool) Source #
Allocate a list of booleans
allocList8 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word8) Source #
Allocate a list of 8-bit values.
allocList16 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word16) Source #
Allocate a list of 16-bit values.
allocList32 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word32) Source #
Allocate a list of 32-bit values.
allocList64 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) Word64) Source #
Allocate a list of 64-bit words.
allocListPtr :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Mut s) (Maybe (Ptr ('Mut s)))) Source #
Allocate a list of pointers.
class TraverseMsg f where Source #
N.B. this should mostly be considered an implementation detail, but it is exposed because it is used by generated code.
TraverseMsg
is similar to 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 for two reasons:
- While algebraically it makes sense, it would be very unintuitive to
e.g. have the
Traversable
instance forList
not traverse over the *elements* of the list. - For the instance for WordPtr, we actually need a stronger constraint than
Applicative in order for the implementation to type check. A previous
version of the library *did* have
tMsg :: Applicative m => ...
, but performance considerations eventually forced us to open up the hood a bit.
tMsg :: TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> f mutA -> m (f mutB) Source #
Instances
TraverseMsg WordPtr Source # | |
Defined in Capnp.Untyped tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> WordPtr mutA -> m (WordPtr mutB) Source # | |
TraverseMsg Struct Source # | |
Defined in Capnp.Untyped tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Struct mutA -> m (Struct mutB) Source # | |
TraverseMsg Cap Source # | |
Defined in Capnp.Untyped tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Cap mutA -> m (Cap mutB) Source # | |
TraverseMsg List Source # | |
Defined in Capnp.Untyped tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> List mutA -> m (List mutB) Source # | |
TraverseMsg Ptr Source # | |
Defined in Capnp.Untyped tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> Ptr mutA -> m (Ptr mutB) Source # |
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 # |