| Safe Haskell | Safe-Inferred | 
|---|---|
| Language | Haskell2010 | 
Capnp.Repr
Contents
- Type-level descriptions of wire representations.
- Mapping representations to value types from Capnp.Untyped
- Mapping types to their wire representations.
- Relating the representations of lists & their elements.
- Working with pointers
- Working with wire-encoded values
- Working with lists
- Allocating values
- Shorthands for types
Description
This module provides facilities for working with the wire
 representations of capnproto objects at the type level. The most
 central part of this module is the Repr type.
Recommended reading: https://capnproto.org/encoding.html
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 ...
- type family ReprFor (a :: Type) :: Repr
- type family PtrReprFor (r :: Repr) :: Maybe PtrRepr where ...
- class Element (r :: Repr) where
- 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)
 
- newtype Raw (a :: Type) (mut :: Mutability) = Raw {}
- data List a
- length :: ListElem a => Raw (List a) mut -> Int
- index :: forall a m mut. (ReadCtx m mut, HasMessage (ListOf (ElemRepr (ListReprFor (ReprFor a)))), ListElem a) => Int -> Raw (List a) mut -> m (Raw a mut)
- setIndex :: forall a m s. (RWCtx m s, ListItem (ElemRepr (ListReprFor (ReprFor a))), Element (ReprFor a)) => Raw a ('Mut s) -> Int -> Raw (List a) ('Mut s) -> m ()
- class Allocate (r :: PtrRepr) where
- type IsStruct a = ReprFor a ~ 'Ptr ('Just 'Struct)
- type IsCap a = ReprFor a ~ 'Ptr ('Just 'Cap)
- type IsPtr a = (ReprFor a ~ 'Ptr (PtrReprFor (ReprFor a)), Untyped (ReprFor a) ~ UntypedPtr (PtrReprFor (ReprFor a)), IsPtrRepr (PtrReprFor (ReprFor a)))
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
Constructors
| Cap | Capability pointer. | 
| List (Maybe ListRepr) | List pointer.  | 
| Struct | A struct (or group). | 
Instances
Information about the representation of a list type.
Constructors
| 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.
Constructors
| NormalListData :: DataSz -> NormalListRepr | |
| NormalListPtr :: NormalListRepr | 
Instances
| Show NormalListRepr Source # | |
| Defined in Capnp.Untyped Methods 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 from Capnp.Untyped
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
 Mutability -> TypeUntyped rUntyped 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 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...
Equations
| 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.
Equations
| 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.
Equations
| UntypedPtr 'Nothing = MaybePtr | |
| UntypedPtr ('Just r) = UntypedSomePtr r | 
type family UntypedSomePtr (r :: PtrRepr) :: Mutability -> Type where ... Source #
Like UntypedPtr, but doesn't allow AnyPointers.
Equations
| 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.
Equations
| UntypedList 'Nothing = List | |
| UntypedList ('Just r) = UntypedSomeList r | 
type family UntypedSomeList (r :: ListRepr) :: Mutability -> Type where ... Source #
Like UntypedList, but doesn't allow AnyLists.
Equations
| UntypedSomeList r = ListOf (ElemRepr r) | 
Mapping types to their wire representations.
type family ReprFor (a :: Type) :: Repr Source #
ReprFor aa.
Instances
type family PtrReprFor (r :: Repr) :: Maybe PtrRepr where ... Source #
PtrReprFor r extracts the pointer represnetation in r; undefined if
 r is not a pointer representation.
Equations
| PtrReprFor ('Ptr pr) = pr | 
Relating the representations of lists & their elements.
class Element (r :: Repr) where Source #
Element supports converting between 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 ElemRepr (ListReprFor r) ~ rListReprFor rfromElement will throw an error.
toElement is more trivial.
Methods
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
type family ElemRepr (rl :: ListRepr) :: Repr where ... Source #
ElemRepr r is the representation of elements of lists with
 representation r.
Equations
| 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.
Equations
| 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.
Methods
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.
Methods
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
Working with wire-encoded values
newtype Raw (a :: Type) (mut :: Mutability) Source #
A Raw mut aa embedded in a capnproto message with mutability
 mut.
Instances
Working with lists
A phantom type denoting capnproto lists of type a.
Instances
index :: forall a m mut. (ReadCtx m mut, HasMessage (ListOf (ElemRepr (ListReprFor (ReprFor a)))), ListElem a) => Int -> Raw (List a) mut -> m (Raw a mut) Source #
index i listith element of the list.
setIndex :: forall a m s. (RWCtx m s, ListItem (ElemRepr (ListReprFor (ReprFor a))), Element (ReprFor a)) => Raw a ('Mut s) -> Int -> Raw (List a) ('Mut s) -> m () Source #
setIndex value i listith element of list to value.
Allocating values
class Allocate (r :: PtrRepr) where Source #
An instace of Allocate'List 'Nothing is missing an instance.
Associated Types
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.
Methods
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 | |
Shorthands for types
type IsPtr a = (ReprFor a ~ 'Ptr (PtrReprFor (ReprFor a)), Untyped (ReprFor a) ~ UntypedPtr (PtrReprFor (ReprFor a)), IsPtrRepr (PtrReprFor (ReprFor a))) Source #
Constraint that a is a pointer type.