capnp-0.18.0.0: Cap'n Proto for Haskell
Safe HaskellSafe-Inferred
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.Untyped

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.Untyped

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

HasMessage (ListOf ('Ptr ('Just 'Struct))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

message :: forall (mut :: Mutability). Unwrapped (ListOf ('Ptr ('Just 'Struct)) mut) -> Message mut Source #

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Ptr ('Just 'Struct)) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Ptr ('Just 'Struct)) mut -> m (Unwrapped (Untyped ('Ptr ('Just 'Struct)) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Ptr ('Just 'Struct)) ('Mut s))) => a -> Int -> ListOf ('Ptr ('Just 'Struct)) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Ptr ('Just 'Struct)) mut -> ListOf ('Ptr ('Just 'Struct)) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Ptr ('Just 'Struct)) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Ptr ('Just 'Struct)) ('Mut s) -> ListOf ('Ptr ('Just 'Struct)) ('Mut s) -> m () Source #

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

Defined in Capnp.Untyped

Methods

length :: forall (mut :: Mutability). ListOf ('Ptr 'Nothing) mut -> Int Source #

unsafeIndex :: forall m (mut :: Mutability). ReadCtx m mut => Int -> ListOf ('Ptr 'Nothing) mut -> m (Unwrapped (Untyped ('Ptr 'Nothing) mut)) Source #

unsafeSetIndex :: (RWCtx m s, a ~ Unwrapped (Untyped ('Ptr 'Nothing) ('Mut s))) => a -> Int -> ListOf ('Ptr 'Nothing) ('Mut s) -> m () Source #

unsafeTake :: forall (mut :: Mutability). Int -> ListOf ('Ptr 'Nothing) mut -> ListOf ('Ptr 'Nothing) mut Source #

checkListOf :: forall m (mut :: Mutability). ReadCtx m mut => ListOf ('Ptr 'Nothing) mut -> m () Source #

copyListOf :: RWCtx m s => ListOf ('Ptr 'Nothing) ('Mut s) -> ListOf ('Ptr 'Nothing) ('Mut s) -> m () Source #

MessageDefault (ListOf ('Ptr ('Just 'Struct))) Source # 
Instance details

Defined in Capnp.Untyped

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (ListOf ('Ptr ('Just 'Struct)) mut)) Source #

IsPtrRepr ('Just 'Cap) Source # 
Instance details

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

IsPtrRepr ('Just 'Struct) Source # 
Instance details

Defined in Capnp.Untyped

Methods

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

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

data ListRepr where Source #

Information about the representation of a list type.

Constructors

ListNormal :: NormalListRepr -> ListRepr

A "normal" list

ListComposite :: ListRepr

A composite (struct) list

Instances

Instances details
Show ListRepr Source # 
Instance details

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

Associated Types

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

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

Defined in Capnp.Untyped

Associated Types

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

Methods

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

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

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

Defined in Capnp.Untyped

type AllocHint ('List ('Just ('ListNormal r))) = Int

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.Untyped

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.Untyped

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 -> Type. This is important, as it allows us to define instances on Untyped r, and use Untyped r in constraints.

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) as the type we really want in some places, though we can't curry it then.

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.

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

Like Untyped, but for pointers only.

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

Like UntypedPtr, but doesn't allow AnyPointers.

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

Like Untyped, but for lists only.

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 a denotes the Cap'n Proto wire represent of the type a.

Instances

Instances details
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 Int8 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor Int8 = 'Data 'Sz8
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 Word8 Source # 
Instance details

Defined in Capnp.Repr

type ReprFor AnyList Source # 
Instance details

Defined in Capnp.Basics

type ReprFor AnyPointer Source # 
Instance details

Defined in Capnp.Basics

type ReprFor AnyStruct Source # 
Instance details

Defined in Capnp.Basics

type ReprFor Capability Source # 
Instance details

Defined in Capnp.Basics

type ReprFor Data Source # 
Instance details

Defined in Capnp.Basics

type ReprFor Text Source # 
Instance details

Defined in Capnp.Basics

type ReprFor DiscriminatorOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type ReprFor FlattenOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type ReprFor Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type ReprFor Value'Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type ReprFor Value'Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type ReprFor Accept Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Bootstrap Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

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

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor CapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Disembargo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Disembargo'context Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Exception Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Exception'Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Finish Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Join Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

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

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor MessageTarget Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Payload Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor PromisedAnswer Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor PromisedAnswer'Op Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Provide Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Release Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Resolve Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor Return Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor ThirdPartyCapDescriptor Source # 
Instance details

Defined in Capnp.Gen.Capnp.Rpc

type ReprFor JoinKeyPart Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

type ReprFor JoinResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

type ReprFor ProvisionId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

type ReprFor RecipientId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

type ReprFor Side Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

type ReprFor ThirdPartyCapId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

type ReprFor VatId Source # 
Instance details

Defined in Capnp.Gen.Capnp.RpcTwoparty

type ReprFor Annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Brand Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Brand'Binding Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Brand'Scope Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor CapnpVersion Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor CodeGeneratorRequest Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor CodeGeneratorRequest'RequestedFile Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor CodeGeneratorRequest'RequestedFile'Import Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Enumerant Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Field'group Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Field'ordinal Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Field'slot Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Method Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Node Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Node'Parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Node'SourceInfo Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Node'SourceInfo'Member Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Node'annotation Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Node'const Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Node'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Node'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Node'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Superclass Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Type Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Type'anyPointer'implicitMethodParameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Type'anyPointer'parameter Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Type'anyPointer'unconstrained Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Type'enum Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Type'interface Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Type'list Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Type'struct Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

type ReprFor StreamResult Source # 
Instance details

Defined in Capnp.Gen.Capnp.Stream

type ReprFor () Source # 
Instance details

Defined in Capnp.Repr

type ReprFor () = 'Data 'Sz0
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 (Which a) Source # 
Instance details

Defined in Capnp.Fields

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

Defined in Capnp.Repr

type ReprFor (List a) = 'Ptr ('Just ('List ('Just (ListReprFor (ReprFor a)))))
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 (Struct mut) Source # 
Instance details

Defined in Capnp.Repr

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

Defined in Capnp.Basics

type ReprFor (Persistent sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

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

Defined in Capnp.Gen.Capnp.Persistent

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

Defined in Capnp.Gen.Capnp.Persistent

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

Defined in Capnp.Repr

type ReprFor (ListOf r mut) = 'Ptr ('Just ('List ('Just (ListReprFor r))))
type ReprFor (RealmGateway internalRef externalRef internalOwner externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent

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

Defined in Capnp.Gen.Capnp.Persistent

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

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

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) 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 -> 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

Instances details
Element ('Data sz) Source # 
Instance details

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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.

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

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

Defined in Capnp.Untyped

Methods

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

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

IsPtrRepr ('Just 'Cap) Source # 
Instance details

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

Defined in Capnp.Untyped

Methods

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

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

IsPtrRepr ('Just 'Struct) Source # 
Instance details

Defined in Capnp.Untyped

Methods

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

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

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

Instances details
IsListPtrRepr 'ListComposite Source # 
Instance details

Defined in Capnp.Untyped

Methods

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

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

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

Defined in Capnp.Untyped

Methods

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

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

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

IsListPtrRepr ('ListNormal 'NormalListPtr) Source # 
Instance details

Defined in Capnp.Untyped

Methods

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

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

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

Working with wire-encoded values

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

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

Constructors

Raw 

Fields

Instances

Instances details
ReprMaybeMutable (ReprFor a) => MaybeMutable (Raw a) Source # 
Instance details

Defined in Capnp.Repr

Methods

thaw :: (PrimMonad m, PrimState m ~ s) => Raw a 'Const -> m (Raw a ('Mut s)) Source #

freeze :: (PrimMonad m, PrimState m ~ s) => Raw a ('Mut s) -> m (Raw a 'Const) Source #

unsafeThaw :: (PrimMonad m, PrimState m ~ s) => Raw a 'Const -> m (Raw a ('Mut s)) Source #

unsafeFreeze :: (PrimMonad m, PrimState m ~ s) => Raw a ('Mut s) -> m (Raw a 'Const) Source #

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

Defined in Capnp.Repr

Methods

message :: forall (mut :: Mutability). Unwrapped (Raw a mut) -> Message mut Source #

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

Defined in Capnp.Repr

Methods

messageDefault :: forall m (mut :: Mutability). ReadCtx m mut => Message mut -> m (Unwrapped (Raw a mut)) Source #

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

Defined in Capnp.Repr

Associated Types

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

Methods

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

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

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

Defined in Capnp.Repr

Methods

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

readList :: ReadS [Raw a mut] #

readPrec :: ReadPrec (Raw a mut) #

readListPrec :: ReadPrec [Raw a mut] #

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

Defined in Capnp.Repr

Methods

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

show :: Raw a mut -> String #

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

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

Defined in Capnp.Repr

Methods

def :: Raw a 'Const #

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

Defined in Capnp.Repr

Methods

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

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

type Rep (Raw a mut) Source # 
Instance details

Defined in Capnp.Repr

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

Working with lists

data List a Source #

A phantom type denoting capnproto lists of type a.

Instances

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Rpc

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Compat.Json

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Rpc

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

Defined in Capnp.Gen.Capnp.Compat.Json

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Compat.Json

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

Defined in Capnp.Classes

Associated Types

type AllocHint (List a) Source #

Methods

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

AllocateList (List a) Source # 
Instance details

Defined in Capnp.Classes

Associated Types

type ListAllocHint (List a) Source #

Methods

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

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

Defined in Capnp.Classes

Methods

estimateAlloc :: [ap] -> AllocHint (List a) Source #

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

Defined in Capnp.Classes

Methods

estimateListAlloc :: [[ap]] -> AllocHint (List (List a)) Source #

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

Defined in Capnp.Classes

Methods

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

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

Defined in Capnp.Classes

Methods

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

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

type AllocHint (List a) Source # 
Instance details

Defined in Capnp.Classes

type ListAllocHint (List a) Source # 
Instance details

Defined in Capnp.Classes

type ReprFor (List a) Source # 
Instance details

Defined in Capnp.Repr

type ReprFor (List a) = 'Ptr ('Just ('List ('Just (ListReprFor (ReprFor a)))))

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

Get the length of a capnproto list.

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 list gets the ith 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 list sets the ith element of list to value.

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

Allocate a value of the given type.

Instances

Instances details
Allocate 'Cap Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type AllocHint 'Cap Source #

Methods

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

Allocate 'Struct Source # 
Instance details

Defined in Capnp.Untyped

Associated Types

type AllocHint 'Struct Source #

Methods

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

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

Defined in Capnp.Untyped

Associated Types

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

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

Defined in Capnp.Untyped

Associated Types

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

Methods

alloc :: RWCtx m s => Message ('Mut s) -> AllocHint ('List ('Just ('ListNormal r))) -> m (Unwrapped (UntypedSomePtr ('List ('Just ('ListNormal r))) ('Mut s))) 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)), Untyped (ReprFor a) ~ UntypedPtr (PtrReprFor (ReprFor a)), IsPtrRepr (PtrReprFor (ReprFor a))) Source #

Constraint that a is a pointer type.