capnp-0.11.0.0: Cap'n Proto for Haskell
Safe HaskellNone
LanguageHaskell2010

Capnp.Repr

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

Type-level descriptions of wire representations.

data Repr Source #

A Repr describes a wire representation for a value. This is mostly used at the type level (using DataKinds); types are parametrized over representations.

Constructors

Ptr (Maybe PtrRepr)

Pointer type. Nothing indicates an AnyPointer, Just describes a more specific pointer type.

Data DataSz

Non-pointer type.

Instances

Instances details
Show Repr Source # 
Instance details

Defined in Capnp.Repr

Methods

showsPrec :: Int -> Repr -> ShowS #

show :: Repr -> String #

showList :: [Repr] -> ShowS #

data PtrRepr Source #

Information about the representation of a pointer type

Constructors

Cap

Capability pointer.

List (Maybe ListRepr)

List pointer. Nothing describes an AnyList, Just describes more specific list types.

Struct

A struct (or group).

Instances

Instances details
Show PtrRepr Source # 
Instance details

Defined in Capnp.Repr

IsPtrRepr ('Nothing :: Maybe PtrRepr) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr 'Nothing) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr 'Nothing)) Source #

Element ('Ptr ('Nothing :: Maybe PtrRepr)) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor ('Ptr 'Nothing))) -> m (Untyped mut ('Ptr 'Nothing)) Source #

toElement :: forall (mut :: Mutability). Untyped mut ('Ptr 'Nothing) -> Untyped mut (ElemRepr (ListReprFor ('Ptr 'Nothing))) Source #

Element ('Ptr ('Just 'Cap)) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just 'Cap)))) -> m (Untyped mut ('Ptr ('Just 'Cap))) Source #

toElement :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just 'Cap)) -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just 'Cap)))) Source #

IsPtrRepr ('Just ('List a)) => Element ('Ptr ('Just ('List a))) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just ('List a))))) -> m (Untyped mut ('Ptr ('Just ('List a)))) Source #

toElement :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just ('List a))) -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just ('List a))))) Source #

Element ('Ptr ('Just 'Struct)) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just 'Struct)))) -> m (Untyped mut ('Ptr ('Just 'Struct))) Source #

toElement :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just 'Struct)) -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just 'Struct)))) Source #

IsPtrRepr ('Just 'Cap) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just 'Cap)) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just 'Cap))) Source #

IsPtrRepr ('Just ('List ('Nothing :: Maybe ListRepr))) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just ('List 'Nothing))) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just ('List 'Nothing)))) Source #

IsListPtrRepr r => IsPtrRepr ('Just ('List ('Just r))) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just ('List ('Just r)))) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just ('List ('Just r))))) Source #

IsPtrRepr ('Just 'Struct) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just 'Struct)) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just 'Struct))) Source #

data ListRepr where Source #

Information about the representation of a list type.

Constructors

ListNormal :: NormalListRepr -> ListRepr

A "normal" list

ListComposite :: ListRepr 

Instances

Instances details
Show ListRepr Source # 
Instance details

Defined in Capnp.Repr

AllocateNormalList r => Allocate ('List ('Just ('ListNormal r))) Source # 
Instance details

Defined in Capnp.Repr

Associated Types

type AllocHint ('List ('Just ('ListNormal r))) Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint ('List ('Just ('ListNormal r))) -> m (UntypedSomePtr ('Mut s) ('List ('Just ('ListNormal r)))) Source #

Allocate ('List ('Just 'ListComposite)) Source # 
Instance details

Defined in Capnp.Repr

Associated Types

type AllocHint ('List ('Just 'ListComposite)) Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint ('List ('Just 'ListComposite)) -> m (UntypedSomePtr ('Mut s) ('List ('Just 'ListComposite))) Source #

IsPtrRepr ('Just ('List ('Nothing :: Maybe ListRepr))) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just ('List 'Nothing))) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just ('List 'Nothing)))) Source #

IsListPtrRepr r => IsPtrRepr ('Just ('List ('Just r))) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just ('List ('Just r)))) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just ('List ('Just r))))) Source #

type AllocHint ('List ('Just ('ListNormal r))) Source # 
Instance details

Defined in Capnp.Repr

type AllocHint ('List ('Just ('ListNormal r))) = Int
type AllocHint ('List ('Just 'ListComposite)) Source # 
Instance details

Defined in Capnp.Repr

data NormalListRepr where Source #

Information about the representation of a normal (non-composite) list.

Instances

Instances details
Show NormalListRepr Source # 
Instance details

Defined in Capnp.Repr

data DataSz Source #

The size of a non-pointer type. SzN represents an N-bit value.

Constructors

Sz0 
Sz1 
Sz8 
Sz16 
Sz32 
Sz64 

Instances

Instances details
Show DataSz Source # 
Instance details

Defined in Capnp.Repr

Mapping representations to value types from Capnp.Untyped

type family Untyped (mut :: Mutability) (r :: Repr) :: Type where ... Source #

Untyped mut r is an untyped value with representation r stored in a message with mutability mut.

Equations

Untyped mut ('Data sz) = UntypedData sz 
Untyped mut ('Ptr ptr) = UntypedPtr mut ptr 

type family UntypedData (sz :: DataSz) :: Type where ... Source #

UntypedData sz is an untyped value with size sz.

type family UntypedPtr (mut :: Mutability) (r :: Maybe PtrRepr) :: Type where ... Source #

Like Untyped, but for pointers only.

Equations

UntypedPtr mut 'Nothing = Maybe (Ptr mut) 
UntypedPtr mut ('Just r) = UntypedSomePtr mut r 

type family UntypedSomePtr (mut :: Mutability) (r :: PtrRepr) :: Type where ... Source #

Like UntypedPtr, but doesn't allow AnyPointers.

Equations

UntypedSomePtr mut 'Struct = Struct mut 
UntypedSomePtr mut 'Cap = Cap mut 
UntypedSomePtr mut ('List r) = UntypedList mut r 

type family UntypedList (mut :: Mutability) (r :: Maybe ListRepr) :: Type where ... Source #

Like Untyped, but for lists only.

Equations

UntypedList mut 'Nothing = List mut 
UntypedList mut ('Just r) = UntypedSomeList mut r 

type family UntypedSomeList (mut :: Mutability) (r :: ListRepr) :: Type where ... Source #

Like UntypedList, but doesn't allow AnyLists.

Equations

UntypedSomeList mut r = ListOf mut (Untyped mut (ElemRepr r)) 

Mapping types to their wire representations.

type family ReprFor (a :: Type) :: Repr Source #

ReprFor a denotes the Cap'n Proto wire represent of the type a.

Instances

Instances details
type ReprFor Bool Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Bool = 'Data 'Sz1
type ReprFor Double Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Float Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Int8 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Int8 = 'Data 'Sz8
type ReprFor Int16 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Int32 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Int64 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Word8 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Word16 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Word32 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Word64 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor () Source # 
Instance details

Defined in Capnp.Repr

type ReprFor () = 'Data 'Sz0
type ReprFor Capability Source # 
Instance details

Defined in Capnp.New.Basics

type ReprFor AnyStruct Source # 
Instance details

Defined in Capnp.New.Basics

type ReprFor AnyList Source # 
Instance details

Defined in Capnp.New.Basics

type ReprFor AnyPointer Source # 
Instance details

Defined in Capnp.New.Basics

type ReprFor Data Source # 
Instance details

Defined in Capnp.New.Basics

type ReprFor Text Source # 
Instance details

Defined in Capnp.New.Basics

type ReprFor StreamResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream.New

type ReprFor CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor CapnpVersion Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Brand'Binding Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Brand'Scope Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type'anyPointer'implicitMethodParameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type'anyPointer'parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type'anyPointer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type'list Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Type = 'Ptr ('Just 'Struct)
type ReprFor Method Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Superclass Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Enumerant Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Field'ordinal Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Field'group Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Field'slot Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node'SourceInfo'Member Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node'SourceInfo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node'NestedNode Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node'Parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node'annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node'const Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

type ReprFor Node = 'Ptr ('Just 'Struct)
type ReprFor JoinResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

type ReprFor JoinKeyPart Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

type ReprFor ThirdPartyCapId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

type ReprFor RecipientId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

type ReprFor ProvisionId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

type ReprFor VatId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

type ReprFor Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty.New

type ReprFor Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor PromisedAnswer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor CapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Payload Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Join Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Join = 'Ptr ('Just 'Struct)
type ReprFor Accept Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Provide Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Disembargo'context Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Disembargo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Release Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Resolve Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Finish Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Return Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Call'sendResultsTo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Call = 'Ptr ('Just 'Struct)
type ReprFor Bootstrap Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor Message Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

type ReprFor DiscriminatorOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

type ReprFor FlattenOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

type ReprFor Value'Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

type ReprFor Value'Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

type ReprFor Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

type ReprFor (Struct mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (Struct mut) = 'Ptr ('Just 'Struct)
type ReprFor (Cap mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (Cap mut) = 'Ptr ('Just 'Cap)
type ReprFor (List mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (List mut) = 'Ptr ('Just ('List ('Nothing :: Maybe ListRepr)))
type ReprFor (Ptr mut) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (Ptr mut) = 'Ptr ('Nothing :: Maybe PtrRepr)
type ReprFor (List a) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (List a) = 'Ptr ('Just ('List ('Just (ListReprFor (ReprFor a)))))
type ReprFor (Which a) Source # 
Instance details

Defined in Capnp.Fields

type ReprFor (Which a) = 'Ptr ('Just 'Struct)
type ReprFor (ListOf mut a) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (ListOf mut a) = ReprFor (List a)
type ReprFor (Persistent'SaveResults sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

type ReprFor (Persistent'SaveResults sturdyRef owner) = 'Ptr ('Just 'Struct)
type ReprFor (Persistent'SaveParams sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

type ReprFor (Persistent'SaveParams sturdyRef owner) = 'Ptr ('Just 'Struct)
type ReprFor (Persistent sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

type ReprFor (Persistent sturdyRef owner) = 'Ptr ('Just 'Cap)
type ReprFor (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

type ReprFor (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) = 'Ptr ('Just 'Struct)
type ReprFor (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

type ReprFor (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) = 'Ptr ('Just 'Struct)
type ReprFor (RealmGateway internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

type ReprFor (RealmGateway internalRef externalRef internalOwner externalOwner) = 'Ptr ('Just 'Cap)

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.

type family ElemRepr (rl :: ListRepr) :: Repr where ... Source #

ElemRepr r is the representation of elements of lists with representation r.

type family ListReprFor (e :: Repr) :: ListRepr where ... Source #

ListReprFor e is the representation of lists with elements whose representation is e.

class Element (r :: Repr) where Source #

Element supports converting between values of representation ElemRepr (ListReprFor r) and values of representation 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) ~ r; in the case of pointer types, ListReprFor 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, fromElement will throw an error.

toElement is more trivial.

Methods

fromElement :: forall m mut. ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor r)) -> m (Untyped mut r) Source #

toElement :: Untyped mut r -> Untyped mut (ElemRepr (ListReprFor r)) Source #

Instances

Instances details
Element ('Ptr ('Nothing :: Maybe PtrRepr)) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor ('Ptr 'Nothing))) -> m (Untyped mut ('Ptr 'Nothing)) Source #

toElement :: forall (mut :: Mutability). Untyped mut ('Ptr 'Nothing) -> Untyped mut (ElemRepr (ListReprFor ('Ptr 'Nothing))) Source #

Element ('Ptr ('Just 'Cap)) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just 'Cap)))) -> m (Untyped mut ('Ptr ('Just 'Cap))) Source #

toElement :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just 'Cap)) -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just 'Cap)))) Source #

IsPtrRepr ('Just ('List a)) => Element ('Ptr ('Just ('List a))) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just ('List a))))) -> m (Untyped mut ('Ptr ('Just ('List a)))) Source #

toElement :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just ('List a))) -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just ('List a))))) Source #

Element ('Ptr ('Just 'Struct)) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just 'Struct)))) -> m (Untyped mut ('Ptr ('Just 'Struct))) Source #

toElement :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just 'Struct)) -> Untyped mut (ElemRepr (ListReprFor ('Ptr ('Just 'Struct)))) Source #

Element ('Data sz) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromElement :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Untyped mut (ElemRepr (ListReprFor ('Data sz))) -> m (Untyped mut ('Data sz)) Source #

toElement :: forall (mut :: Mutability). Untyped mut ('Data sz) -> Untyped mut (ElemRepr (ListReprFor ('Data sz))) Source #

Working with wire-encoded values

newtype Raw (mut :: Mutability) (a :: Type) Source #

A Raw mut a is an a embedded in a capnproto message with mutability mut.

Constructors

Raw 

Fields

Instances

Instances details
ReprFor a ~ 'Ptr ('Just 'Struct) => ToStruct mut (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

toStruct :: Raw mut a -> Struct mut Source #

ReprFor a ~ 'Ptr ('Just 'Struct) => FromStruct mut (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromStruct :: ReadCtx m mut => Struct mut -> m (Raw mut a) Source #

(IsPtrRepr r, ReprFor a ~ 'Ptr r) => ToPtr s (Raw ('Mut s) a) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: WriteCtx m s => Message ('Mut s) -> Raw ('Mut s) a -> m (Maybe (Ptr ('Mut s))) Source #

(IsPtrRepr r, ReprFor a ~ 'Ptr r) => FromPtr mut (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

fromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Raw mut a) Source #

Eq (Untyped mut (ReprFor a)) => Eq (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

(==) :: Raw mut a -> Raw mut a -> Bool #

(/=) :: Raw mut a -> Raw mut a -> Bool #

Read (Untyped mut (ReprFor a)) => Read (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

readsPrec :: Int -> ReadS (Raw mut a) #

readList :: ReadS [Raw mut a] #

readPrec :: ReadPrec (Raw mut a) #

readListPrec :: ReadPrec [Raw mut a] #

Show (Untyped mut (ReprFor a)) => Show (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Methods

showsPrec :: Int -> Raw mut a -> ShowS #

show :: Raw mut a -> String #

showList :: [Raw mut a] -> ShowS #

Generic (Untyped mut (ReprFor a)) => Generic (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

Associated Types

type Rep (Raw mut a) :: Type -> Type #

Methods

from :: Raw mut a -> Rep (Raw mut a) x #

to :: Rep (Raw mut a) x -> Raw mut a #

MessageDefault (Raw 'Const a) 'Const => Default (Raw 'Const a) Source # 
Instance details

Defined in Capnp.Repr

Methods

def :: Raw 'Const a #

MessageDefault (Untyped mut (ReprFor a)) mut => MessageDefault (Raw mut a) mut Source # 
Instance details

Defined in Capnp.Repr

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Raw mut a) Source #

HasMessage (Untyped mut (ReprFor a)) mut => HasMessage (Raw mut a) mut Source # 
Instance details

Defined in Capnp.Repr

Methods

message :: Raw mut a -> Message mut Source #

type Rep (Raw mut a) Source # 
Instance details

Defined in Capnp.Repr

type Rep (Raw mut a) = D1 ('MetaData "Raw" "Capnp.Repr" "capnp-0.11.0.0-50ovYl0NjrHDYHPSniP5DX" 'True) (C1 ('MetaCons "Raw" 'PrefixI 'True) (S1 ('MetaSel ('Just "fromRaw") 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 (Untyped mut (ReprFor a)))))

Working with lists

data List a Source #

A phantom type denoting capnproto lists of type a.

Instances

Instances details
HasVariant "array" 'Slot Value (List Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasVariant "bind" 'Slot Brand'Scope (List Brand'Binding) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasVariant "object" 'Slot Value (List Value'Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "annotations" 'Slot Method (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "annotations" 'Slot Enumerant (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "annotations" 'Slot Field (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "annotations" 'Slot Node (List Annotation) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "capTable" 'Slot Payload (List CapDescriptor) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

HasField "enumerants" 'Slot Node'enum (List Enumerant) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "fields" 'Slot Node'struct (List Field) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "implicitParameters" 'Slot Method (List Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "imports" 'Slot CodeGeneratorRequest'RequestedFile (List CodeGeneratorRequest'RequestedFile'Import) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "members" 'Slot Node'SourceInfo (List Node'SourceInfo'Member) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "methods" 'Slot Node'interface (List Method) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "nestedNodes" 'Slot Node (List Node'NestedNode) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "nodes" 'Slot CodeGeneratorRequest (List Node) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "parameters" 'Slot Node (List Node'Parameter) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "params" 'Slot Value'Call (List Value) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json.New

HasField "requestedFiles" 'Slot CodeGeneratorRequest (List CodeGeneratorRequest'RequestedFile) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "scopes" 'Slot Brand (List Brand'Scope) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "sourceInfo" 'Slot CodeGeneratorRequest (List Node'SourceInfo) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "superclasses" 'Slot Node'interface (List Superclass) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.New

HasField "transform" 'Slot PromisedAnswer (List PromisedAnswer'Op) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc.New

AllocateList (List a) Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type ListAllocHint (List a) Source #

Methods

newList :: RWCtx m s => ListAllocHint (List a) -> Message ('Mut s) -> m (Raw ('Mut s) (List (List a))) Source #

AllocateList a => Allocate (List a) Source # 
Instance details

Defined in Capnp.New.Classes

Associated Types

type AllocHint (List a) Source #

Methods

new :: RWCtx m s => AllocHint (List a) -> Message ('Mut s) -> m (Raw ('Mut s) (List a)) Source #

(Parse (List a) (Vector ap), Allocate (List a)) => EstimateListAlloc (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

MarshalElement a ap => Marshal (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

Methods

marshalInto :: RWCtx m s => Raw ('Mut s) (List a) -> Vector ap -> m () Source #

MarshalElement a ap => EstimateAlloc (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

MarshalElement a ap => Parse (List a) (Vector ap) Source # 
Instance details

Defined in Capnp.New.Classes

Methods

parse :: ReadCtx m 'Const => Raw 'Const (List a) -> m (Vector ap) Source #

encode :: RWCtx m s => Message ('Mut s) -> Vector ap -> m (Raw ('Mut s) (List a)) Source #

type ReprFor (List a) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (List a) = 'Ptr ('Just ('List ('Just (ListReprFor (ReprFor a)))))
type ListAllocHint (List a) Source # 
Instance details

Defined in Capnp.New.Classes

type AllocHint (List a) Source # 
Instance details

Defined in Capnp.New.Classes

length :: Raw mut (List a) -> Int Source #

Get the length of a capnproto list.

index :: forall a m mut. (ReadCtx m mut, Element (ReprFor a)) => Int -> Raw mut (List a) -> m (Raw mut a) Source #

index i list gets the ith element of the list.

setIndex :: forall a m s. (RWCtx m s, Element (ReprFor a)) => Raw ('Mut s) a -> Int -> Raw ('Mut s) (List a) -> m () Source #

setIndex value i list sets the ith element of list to value.

Working with pointers

class IsPtrRepr (r :: Maybe PtrRepr) where Source #

Operations on types with pointer representations.

Methods

toPtr :: Untyped mut ('Ptr r) -> Maybe (Ptr mut) Source #

Convert an untyped value of this representation to an AnyPointer.

fromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr r)) Source #

Extract a value with this representation from an AnyPointer, failing if the pointer is the wrong type for this representation.

Instances

Instances details
IsPtrRepr ('Nothing :: Maybe PtrRepr) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr 'Nothing) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr 'Nothing)) Source #

IsPtrRepr ('Just 'Cap) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just 'Cap)) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just 'Cap))) Source #

IsPtrRepr ('Just ('List ('Nothing :: Maybe ListRepr))) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just ('List 'Nothing))) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just ('List 'Nothing)))) Source #

IsListPtrRepr r => IsPtrRepr ('Just ('List ('Just r))) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just ('List ('Just r)))) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just ('List ('Just r))))) Source #

IsPtrRepr ('Just 'Struct) Source # 
Instance details

Defined in Capnp.Repr

Methods

toPtr :: forall (mut :: Mutability). Untyped mut ('Ptr ('Just 'Struct)) -> Maybe (Ptr mut) Source #

fromPtr :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (Untyped mut ('Ptr ('Just 'Struct))) Source #

class IsListPtrRepr (r :: ListRepr) where Source #

Operations on types with list representations.

Methods

rToList :: UntypedSomeList mut r -> List mut Source #

Convert an untyped value of this representation to an AnyList.

rFromList :: ReadCtx m mut => List mut -> m (UntypedSomeList mut r) 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 mut r) Source #

Create a zero-length value with this representation, living in the provided message.

Instances

Instances details
IsListPtrRepr 'ListComposite Source # 
Instance details

Defined in Capnp.Repr

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList mut 'ListComposite -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList mut 'ListComposite) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList mut 'ListComposite) Source #

IsListPtrRepr ('ListNormal ('ListData 'Sz0)) Source # 
Instance details

Defined in Capnp.Repr

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList mut ('ListNormal ('ListData 'Sz0)) -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz0))) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz0))) Source #

IsListPtrRepr ('ListNormal ('ListData 'Sz1)) Source # 
Instance details

Defined in Capnp.Repr

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList mut ('ListNormal ('ListData 'Sz1)) -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz1))) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz1))) Source #

IsListPtrRepr ('ListNormal ('ListData 'Sz8)) Source # 
Instance details

Defined in Capnp.Repr

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList mut ('ListNormal ('ListData 'Sz8)) -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz8))) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz8))) Source #

IsListPtrRepr ('ListNormal ('ListData 'Sz16)) Source # 
Instance details

Defined in Capnp.Repr

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList mut ('ListNormal ('ListData 'Sz16)) -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz16))) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz16))) Source #

IsListPtrRepr ('ListNormal ('ListData 'Sz32)) Source # 
Instance details

Defined in Capnp.Repr

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList mut ('ListNormal ('ListData 'Sz32)) -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz32))) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz32))) Source #

IsListPtrRepr ('ListNormal ('ListData 'Sz64)) Source # 
Instance details

Defined in Capnp.Repr

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList mut ('ListNormal ('ListData 'Sz64)) -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz64))) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList mut ('ListNormal ('ListData 'Sz64))) Source #

IsListPtrRepr ('ListNormal 'ListPtr) Source # 
Instance details

Defined in Capnp.Repr

Methods

rToList :: forall (mut :: Mutability). UntypedSomeList mut ('ListNormal 'ListPtr) -> List mut Source #

rFromList :: forall m (mut :: Mutability). ReadCtx m mut => List mut -> m (UntypedSomeList mut ('ListNormal 'ListPtr)) Source #

rFromListMsg :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (UntypedSomeList mut ('ListNormal 'ListPtr)) Source #

Allocating values

class Allocate (r :: PtrRepr) where Source #

An instace of Allocate 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 'List 'Nothing is missing an instance.

Associated Types

type AllocHint r Source #

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 (UntypedSomePtr ('Mut s) r) Source #

Allocate a value of the given type.

Instances

Instances details
Allocate 'Cap Source # 
Instance details

Defined in Capnp.Repr

Associated Types

type AllocHint 'Cap Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint 'Cap -> m (UntypedSomePtr ('Mut s) 'Cap) Source #

Allocate 'Struct Source # 
Instance details

Defined in Capnp.Repr

Associated Types

type AllocHint 'Struct Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint 'Struct -> m (UntypedSomePtr ('Mut s) 'Struct) Source #

AllocateNormalList r => Allocate ('List ('Just ('ListNormal r))) Source # 
Instance details

Defined in Capnp.Repr

Associated Types

type AllocHint ('List ('Just ('ListNormal r))) Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint ('List ('Just ('ListNormal r))) -> m (UntypedSomePtr ('Mut s) ('List ('Just ('ListNormal r)))) Source #

Allocate ('List ('Just 'ListComposite)) Source # 
Instance details

Defined in Capnp.Repr

Associated Types

type AllocHint ('List ('Just 'ListComposite)) Source #

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint ('List ('Just 'ListComposite)) -> m (UntypedSomePtr ('Mut s) ('List ('Just 'ListComposite))) Source #

Shorthands for types

type IsStruct a = ReprFor a ~ 'Ptr ('Just 'Struct) Source #

Constraint that a is a struct type.

type IsCap a = ReprFor a ~ 'Ptr ('Just 'Cap) Source #

Constraint that a is a capability type.

type IsPtr a = (ReprFor a ~ 'Ptr (PtrReprFor (ReprFor a)), IsPtrRepr (PtrReprFor (ReprFor a))) Source #

Constraint that a is a pointer type.