Safe Haskell | Safe-Inferred |
---|---|
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 Repr
- data PtrRepr
- data ListRepr where
- data NormalListRepr where
- data DataSz
- type family Untyped (r :: Repr) :: Mutability -> Type where ...
- type family UntypedData (sz :: DataSz) :: Type where ...
- type family UntypedPtr (r :: Maybe PtrRepr) :: Mutability -> Type where ...
- type family UntypedSomePtr (r :: PtrRepr) :: Mutability -> Type where ...
- type family UntypedList (r :: Maybe ListRepr) :: Mutability -> Type where ...
- type family UntypedSomeList (r :: ListRepr) :: Mutability -> Type where ...
- newtype IgnoreMut a (mut :: Mutability) = IgnoreMut a
- newtype MaybePtr (mut :: Mutability) = MaybePtr (Maybe (Ptr mut))
- type family Unwrapped a where ...
- class Element (r :: Repr) where
- class Element r => ListItem (r :: Repr) where
- length :: ListOf r mut -> Int
- unsafeIndex :: ReadCtx m mut => Int -> ListOf r mut -> m (Unwrapped (Untyped r mut))
- unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped r ('Mut s))) => a -> Int -> ListOf r ('Mut s) -> m ()
- unsafeTake :: Int -> ListOf r mut -> ListOf r mut
- checkListOf :: ReadCtx m mut => ListOf r mut -> m ()
- copyListOf :: RWCtx m s => ListOf r ('Mut s) -> ListOf r ('Mut s) -> m ()
- type family ElemRepr (rl :: ListRepr) :: Repr where ...
- type family ListReprFor (e :: Repr) :: ListRepr where ...
- class IsPtrRepr (r :: Maybe PtrRepr) where
- class IsListPtrRepr (r :: ListRepr) where
- rToList :: UntypedSomeList r mut -> List mut
- rFromList :: ReadCtx m mut => List mut -> m (UntypedSomeList r mut)
- rFromListMsg :: ReadCtx m mut => Message mut -> m (UntypedSomeList r mut)
- class Allocate (r :: PtrRepr) where
- class AllocateNormalList (r :: NormalListRepr) where
- allocNormalList :: RWCtx m s => Message ('Mut s) -> Int -> m (UntypedSomeList ('ListNormal r) ('Mut s))
- data Ptr mut
- data List mut
- data Struct mut
- data ListOf r mut
- data Cap mut
- structByteCount :: Struct mut -> ByteCount
- structWordCount :: Struct mut -> WordCount
- structPtrCount :: Struct mut -> Word16
- structListByteCount :: ListOf ('Ptr ('Just 'Struct)) mut -> ByteCount
- structListWordCount :: ListOf ('Ptr ('Just 'Struct)) mut -> WordCount
- structListPtrCount :: ListOf ('Ptr ('Just 'Struct)) mut -> 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))
- getClient :: ReadCtx m mut => Cap mut -> m Client
- get :: ReadCtx m mut => WordPtr mut -> m (Maybe (Ptr mut))
- index :: (ReadCtx m mut, ListItem r) => Int -> ListOf r mut -> m (Unwrapped (Untyped r mut))
- setIndex :: (RWCtx m s, ListItem r) => Unwrapped (Untyped r ('Mut s)) -> Int -> ListOf r ('Mut s) -> m ()
- take :: (ListItem r, MonadThrow m) => Int -> ListOf r mut -> m (ListOf r mut)
- rootPtr :: ReadCtx m mut => Message mut -> m (Struct mut)
- setRoot :: WriteCtx m s => Struct ('Mut s) -> m ()
- rawBytes :: ReadCtx m 'Const => ListOf ('Data 'Sz8) 'Const -> 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 (f :: Mutability -> Type) where
- class HasMessage f => MessageDefault f where
- messageDefault :: ReadCtx m mut => Message mut -> m (Unwrapped (f mut))
- 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 ('Ptr ('Just 'Struct)) ('Mut s))
- allocList0 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz0) ('Mut s))
- allocList1 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz1) ('Mut s))
- allocList8 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz8) ('Mut s))
- allocList16 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz16) ('Mut s))
- allocList32 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz32) ('Mut s))
- allocList64 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz64) ('Mut s))
- allocListPtr :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Ptr 'Nothing) ('Mut s))
- appendCap :: WriteCtx m s => Message ('Mut s) -> Client -> m (Cap ('Mut s))
- class TraverseMsg f where
Type-level descriptions of wire representations.
A Repr
describes a wire representation for a value. This is
mostly used at the type level (using DataKinds); types are
parametrized over representations.
Information about the representation of a pointer type
Cap | Capability pointer. |
List (Maybe ListRepr) | List pointer. |
Struct | A struct (or group). |
Instances
Information about the representation of a list type.
ListNormal :: NormalListRepr -> ListRepr | A "normal" list |
ListComposite :: ListRepr | A composite (struct) list |
Instances
Show ListRepr Source # | |
Allocate ('List ('Just 'ListComposite)) Source # | |
Defined in Capnp.Untyped | |
AllocateNormalList r => Allocate ('List ('Just ('ListNormal r))) Source # | |
Defined in Capnp.Untyped | |
IsListPtrRepr r => IsPtrRepr ('Just ('List ('Just r))) Source # | |
Defined in Capnp.Untyped | |
IsPtrRepr ('Just ('List ('Nothing :: Maybe ListRepr))) Source # | |
Defined in Capnp.Untyped | |
type AllocHint ('List ('Just 'ListComposite)) Source # | |
Defined in Capnp.Untyped | |
type AllocHint ('List ('Just ('ListNormal r))) Source # | |
Defined in Capnp.Untyped |
data NormalListRepr where Source #
Information about the representation of a normal (non-composite) list.
Instances
Show NormalListRepr Source # | |
Defined in Capnp.Untyped showsPrec :: Int -> NormalListRepr -> ShowS # show :: NormalListRepr -> String # showList :: [NormalListRepr] -> ShowS # |
The size of a non-pointer type. SzN
represents an N
-bit value.
Mapping representations to value types.
type family Untyped (r :: Repr) :: Mutability -> Type where ... Source #
Untyped r mut
is an untyped value with representation r
stored in
a message with mutability mut
.
Note that the return type of this type family has kind
. This is important, as it allows us
to define instances on Mutability
-> Type
, and use Untyped
r
in constraints.Untyped
r
This introduces some awkwardnesses though -- we really want
this to be (Maybe (Ptr mut))
for 'Ptr 'Nothing
, and
Int typesBool() for 'Data sz
. But we can't because these
are the wrong kind.
So, we hack around this by introducing two newtypes, IgnoreMut
and MaybePtr
, and a type family Unwrapped
, which lets us
use
as the type we really want
in some places, though we can't curry it then.Unwrapped
(Untyped
r mut)
All this is super super awkward, but this is a low level mostly-internal API; most users will intract with this through the Raw type in Capnp.Repr, which hides all of this...
Untyped ('Data sz) = IgnoreMut (UntypedData sz) | |
Untyped ('Ptr ptr) = UntypedPtr ptr |
type family UntypedData (sz :: DataSz) :: Type where ... Source #
UntypedData sz
is an untyped value with size sz
.
UntypedData 'Sz0 = () | |
UntypedData 'Sz1 = Bool | |
UntypedData 'Sz8 = Word8 | |
UntypedData 'Sz16 = Word16 | |
UntypedData 'Sz32 = Word32 | |
UntypedData 'Sz64 = Word64 |
type family UntypedPtr (r :: Maybe PtrRepr) :: Mutability -> Type where ... Source #
Like Untyped
, but for pointers only.
UntypedPtr 'Nothing = MaybePtr | |
UntypedPtr ('Just r) = UntypedSomePtr r |
type family UntypedSomePtr (r :: PtrRepr) :: Mutability -> Type where ... Source #
Like UntypedPtr
, but doesn't allow AnyPointers.
UntypedSomePtr 'Struct = Struct | |
UntypedSomePtr 'Cap = Cap | |
UntypedSomePtr ('List r) = UntypedList r |
type family UntypedList (r :: Maybe ListRepr) :: Mutability -> Type where ... Source #
Like Untyped
, but for lists only.
UntypedList 'Nothing = List | |
UntypedList ('Just r) = UntypedSomeList r |
type family UntypedSomeList (r :: ListRepr) :: Mutability -> Type where ... Source #
Like UntypedList
, but doesn't allow AnyLists.
UntypedSomeList r = ListOf (ElemRepr r) |
newtype IgnoreMut a (mut :: Mutability) Source #
Instances
newtype MaybePtr (mut :: Mutability) Source #
Instances
MaybeMutable MaybePtr Source # | |
Defined in Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => MaybePtr 'Const -> m (MaybePtr ('Mut s)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => MaybePtr ('Mut s) -> m (MaybePtr 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => MaybePtr 'Const -> m (MaybePtr ('Mut s)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => MaybePtr ('Mut s) -> m (MaybePtr 'Const) Source # |
Relating the representations of lists & their elements.
class Element (r :: Repr) where Source #
Element
supports converting between values of representation
and values of representation ElemRepr
(ListReprFor
r)r
.
At a glance, you might expect this to just be a no-op, but it is actually
*not* always the case that
; in the
case of pointer types, ElemRepr
(ListReprFor
r) ~ r
can contain arbitrary pointers,
so information is lost, and it is possible for the list to contain pointers
of the incorrect type. In this case, ListReprFor
rfromElement
will throw an error.
toElement
is more trivial.
fromElement :: forall m mut. ReadCtx m mut => Message mut -> Unwrapped (Untyped (ElemRepr (ListReprFor r)) mut) -> m (Unwrapped (Untyped r mut)) Source #
toElement :: Unwrapped (Untyped r mut) -> Unwrapped (Untyped (ElemRepr (ListReprFor r)) mut) Source #
Instances
class Element r => ListItem (r :: Repr) where Source #
indicates that ListItem
rr
is a representation for elements of some list
type. Not every representation is covered; instances exist only for r
where
.ElemRepr
(ListReprFor
r) ~ r
Nothing
length :: ListOf r mut -> Int Source #
Returns the length of a list
unsafeIndex :: ReadCtx m mut => Int -> ListOf r mut -> m (Unwrapped (Untyped r mut)) Source #
default unsafeIndex :: forall m mut. (ReadCtx m mut, Integral (Unwrapped (Untyped r mut)), ListRepOf r ~ NormalList, FiniteBits (Unwrapped (Untyped r mut))) => Int -> ListOf r mut -> m (Unwrapped (Untyped r mut)) Source #
unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped r ('Mut s))) => a -> Int -> ListOf r ('Mut s) -> m () Source #
default unsafeSetIndex :: forall m s a. (RWCtx m s, a ~ Unwrapped (Untyped r ('Mut s)), ListRepOf r ~ NormalList, Integral a, Bounded a, FiniteBits a) => a -> Int -> ListOf r ('Mut s) -> m () Source #
unsafeTake :: Int -> ListOf r mut -> ListOf r mut Source #
checkListOf :: ReadCtx m mut => ListOf r mut -> m () Source #
default checkListOf :: forall m mut. (ReadCtx m mut, ListRepOf r ~ NormalList, FiniteBits (Untyped r mut)) => ListOf r mut -> m () Source #
copyListOf :: RWCtx m s => ListOf r ('Mut s) -> ListOf r ('Mut s) -> m () Source #
Make a copy of the list, in the target message.
Instances
type family ElemRepr (rl :: ListRepr) :: Repr where ... Source #
ElemRepr r
is the representation of elements of lists with
representation r
.
ElemRepr 'ListComposite = 'Ptr ('Just 'Struct) | |
ElemRepr ('ListNormal 'NormalListPtr) = 'Ptr 'Nothing | |
ElemRepr ('ListNormal ('NormalListData sz)) = 'Data sz |
type family ListReprFor (e :: Repr) :: ListRepr where ... Source #
ListReprFor e
is the representation of lists with elements
whose representation is e
.
ListReprFor ('Data sz) = 'ListNormal ('NormalListData sz) | |
ListReprFor ('Ptr ('Just 'Struct)) = 'ListComposite | |
ListReprFor ('Ptr a) = 'ListNormal 'NormalListPtr |
Working with pointers
class IsPtrRepr (r :: Maybe PtrRepr) where Source #
Operations on types with pointer representations.
toPtr :: Unwrapped (Untyped ('Ptr r) mut) -> Maybe (Ptr mut) Source #
Convert an untyped value of this representation to an AnyPointer.
fromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Unwrapped (Untyped ('Ptr r) mut)) Source #
Extract a value with this representation from an AnyPointer, failing if the pointer is the wrong type for this representation.
Instances
class IsListPtrRepr (r :: ListRepr) where Source #
Operations on types with list representations.
rToList :: UntypedSomeList r mut -> List mut Source #
Convert an untyped value of this representation to an AnyList.
rFromList :: ReadCtx m mut => List mut -> m (UntypedSomeList r mut) Source #
Extract a value with this representation from an AnyList, failing if the list is the wrong type for this representation.
rFromListMsg :: ReadCtx m mut => Message mut -> m (UntypedSomeList r mut) Source #
Create a zero-length value with this representation, living in the provided message.
Instances
Allocating values
class Allocate (r :: PtrRepr) where Source #
An instace of
specifies how to allocate a value with a given representation.
This only makes sense for pointers of course, so it is defined on PtrRepr. Of the well-kinded
types, only Allocate
'List 'Nothing
is missing an instance.
Extra information needed to allocate a value:
- For structs, the sizes of the sections.
- For capabilities, the client to attach to the messages.
- For lists, the length, and for composite lists, the struct sizes as well.
alloc :: RWCtx m s => Message ('Mut s) -> AllocHint r -> m (Unwrapped (UntypedSomePtr r ('Mut s))) Source #
Allocate a value of the given type.
Instances
Allocate 'Cap Source # | |
Allocate 'Struct Source # | |
Allocate ('List ('Just 'ListComposite)) Source # | |
Defined in Capnp.Untyped | |
AllocateNormalList r => Allocate ('List ('Just ('ListNormal r))) Source # | |
Defined in Capnp.Untyped |
class AllocateNormalList (r :: NormalListRepr) where Source #
Like Allocate
, but specialized to normal (non-composite) lists.
Instead of an AllocHint
type family, the hint is always an Int
,
which is the number of elements.
allocNormalList :: RWCtx m s => Message ('Mut s) -> Int -> m (UntypedSomeList ('ListNormal r) ('Mut s)) Source #
Instances
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
MaybeMutable Ptr Source # | |
Defined in Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => Ptr 'Const -> m (Ptr ('Mut s)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Ptr ('Mut s) -> m (Ptr 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Ptr 'Const -> m (Ptr ('Mut s)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Ptr ('Mut s) -> m (Ptr 'Const) Source # | |
HasMessage Ptr Source # | |
Defined in Capnp.Untyped | |
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 # | |
type ReprFor (Ptr mut) Source # | |
A list of values (of arbitrary type) in a message.
List0 (ListOf ('Data 'Sz0) mut) | |
List1 (ListOf ('Data 'Sz1) mut) | |
List8 (ListOf ('Data 'Sz8) mut) | |
List16 (ListOf ('Data 'Sz16) mut) | |
List32 (ListOf ('Data 'Sz32) mut) | |
List64 (ListOf ('Data 'Sz64) mut) | |
ListPtr (ListOf ('Ptr 'Nothing) mut) | |
ListStruct (ListOf ('Ptr ('Just 'Struct)) mut) |
Instances
MaybeMutable List Source # | |
Defined in Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => List 'Const -> m (List ('Mut s)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => List ('Mut s) -> m (List 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => List 'Const -> m (List ('Mut s)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => List ('Mut s) -> m (List 'Const) Source # | |
HasMessage List Source # | |
Defined in Capnp.Untyped | |
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 # | |
type ReprFor (List mut) Source # | |
A struct value in a message.
Instances
MaybeMutable Struct Source # | |
Defined in Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => Struct 'Const -> m (Struct ('Mut s)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Struct ('Mut s) -> m (Struct 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Struct 'Const -> m (Struct ('Mut s)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Struct ('Mut s) -> m (Struct 'Const) Source # | |
HasMessage Struct Source # | |
Defined in Capnp.Untyped | |
MessageDefault Struct Source # | |
Defined in Capnp.Untyped messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (Struct mut)) 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 # | |
type ReprFor (Struct mut) Source # | |
A list of values with representation r
in a message.
Instances
A Capability in a message.
Instances
MaybeMutable Cap Source # | |
Defined in Capnp.Untyped thaw :: (PrimMonad m, PrimState m ~ s) => Cap 'Const -> m (Cap ('Mut s)) Source # freeze :: (PrimMonad m, PrimState m ~ s) => Cap ('Mut s) -> m (Cap 'Const) Source # unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Cap 'Const -> m (Cap ('Mut s)) Source # unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Cap ('Mut s) -> m (Cap 'Const) Source # | |
HasMessage Cap Source # | |
Defined in Capnp.Untyped | |
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 # | |
type ReprFor (Cap mut) Source # | |
structByteCount :: Struct mut -> ByteCount Source #
Get the size (in bytes) of a struct's data section.
structWordCount :: Struct mut -> WordCount Source #
Get the size (in words) of a struct's data section.
structPtrCount :: Struct mut -> Word16 Source #
Get the size of a struct's pointer section.
structListByteCount :: ListOf ('Ptr ('Just 'Struct)) mut -> ByteCount Source #
Get the size (in words) of the data sections in a struct list.
structListWordCount :: ListOf ('Ptr ('Just 'Struct)) mut -> WordCount Source #
Get the size (in words) of the data sections in a struct list.
structListPtrCount :: ListOf ('Ptr ('Just 'Struct)) mut -> 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.
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, ListItem r) => Int -> ListOf r mut -> m (Unwrapped (Untyped r mut)) Source #
index i list
returns the ith element in list
. Deducts 1 from the quota
setIndex :: (RWCtx m s, ListItem r) => Unwrapped (Untyped r ('Mut s)) -> Int -> ListOf r ('Mut s) -> m () Source #
'setIndex value i list
Set the i
th element of list
to value
.
take :: (ListItem r, MonadThrow m) => Int -> ListOf r mut -> m (ListOf r mut) 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 ('Data 'Sz8) 'Const -> 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 (f :: Mutability -> Type) where Source #
Types whose storage is owned by a message..
Instances
HasMessage WordPtr Source # | |
Defined in Capnp.Untyped | |
HasMessage Cap Source # | |
Defined in Capnp.Untyped | |
HasMessage List Source # | |
Defined in Capnp.Untyped | |
HasMessage Ptr Source # | |
Defined in Capnp.Untyped | |
HasMessage Struct Source # | |
Defined in Capnp.Untyped | |
HasMessage (Untyped (ReprFor a)) => HasMessage (Raw a) Source # | |
Defined in Capnp.Repr | |
HasMessage (ListOf ('Ptr ('Just 'Struct))) Source # | |
ListRepOf r ~ NormalList => HasMessage (ListOf r) Source # | |
Defined in Capnp.Untyped |
class HasMessage f => MessageDefault f 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.
Instances
MessageDefault Struct Source # | |
Defined in Capnp.Untyped messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (Struct mut)) Source # | |
MessageDefault (Untyped (ReprFor a)) => MessageDefault (Raw a) Source # | |
Defined in Capnp.Repr messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (Raw a mut)) Source # | |
MessageDefault (ListOf ('Ptr ('Just 'Struct))) Source # | |
Defined in Capnp.Untyped | |
ListRepOf r ~ NormalList => MessageDefault (ListOf r) Source # | |
Defined in Capnp.Untyped messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (ListOf r mut)) Source # |
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 ('Ptr ('Just 'Struct)) ('Mut s)) |
Allocate a composite list.
allocList0 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz0) ('Mut s)) Source #
Allocate a list of capnproto Void
values.
allocList1 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz1) ('Mut s)) Source #
Allocate a list of booleans
allocList8 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz8) ('Mut s)) Source #
Allocate a list of 8-bit values.
allocList16 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz16) ('Mut s)) Source #
Allocate a list of 16-bit values.
allocList32 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz32) ('Mut s)) Source #
Allocate a list of 32-bit values.
allocList64 :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Data 'Sz64) ('Mut s)) Source #
Allocate a list of 64-bit words.
allocListPtr :: WriteCtx m s => Message ('Mut s) -> Int -> m (ListOf ('Ptr 'Nothing) ('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 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 # | |
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 (ListRepOf r) => TraverseMsg (ListOf r) Source # | |
Defined in Capnp.Untyped tMsg :: forall m (mutA :: Mutability) (mutB :: Mutability). TraverseMsgCtx m mutA mutB => (Message mutA -> m (Message mutB)) -> ListOf r mutA -> m (ListOf r mutB) Source # |