capnp-0.2.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Capnp.Capnp.Schema

Description

This module is the generated code for capnp/schema.capnp, for the low-level api.

Documentation

newtype Annotation msg Source #

Constructors

Annotation_newtype_ (Struct msg) 
Instances
ToStruct msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Annotation msg -> Struct msg Source #

FromStruct msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Annotation msg) Source #

IsPtr msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Annotation msg) Source #

toPtr :: Annotation msg -> Maybe (Ptr msg) Source #

Allocate s (Annotation (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Annotation (MutMsg s)) Source #

MutListElem s (Annotation (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Annotation (MutMsg s) -> Int -> List (MutMsg s) (Annotation (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Annotation (MutMsg s))) Source #

ListElem msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Annotation msg) :: * Source #

Methods

length :: List msg (Annotation msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Annotation msg) -> m (Annotation msg) Source #

IsPtr msg (List msg (Annotation msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Annotation msg)) Source #

toPtr :: List msg (Annotation msg) -> Maybe (Ptr msg) Source #

MessageDefault (Annotation msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Annotation msg Source #

HasMessage (Annotation msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Annotation msg -> msg Source #

data List msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Annotation msg) = List_Annotation (ListOf msg (Struct msg))

newtype Brand msg Source #

Constructors

Brand_newtype_ (Struct msg) 
Instances
ToStruct msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Brand msg -> Struct msg Source #

FromStruct msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand msg) Source #

IsPtr msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Brand msg) Source #

toPtr :: Brand msg -> Maybe (Ptr msg) Source #

Allocate s (Brand (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Brand (MutMsg s)) Source #

MutListElem s (Brand (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand (MutMsg s) -> Int -> List (MutMsg s) (Brand (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand (MutMsg s))) Source #

ListElem msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Brand msg) :: * Source #

Methods

length :: List msg (Brand msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Brand msg) -> m (Brand msg) Source #

IsPtr msg (List msg (Brand msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Brand msg)) Source #

toPtr :: List msg (Brand msg) -> Maybe (Ptr msg) Source #

MessageDefault (Brand msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Brand msg Source #

HasMessage (Brand msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Brand msg -> msg Source #

data List msg (Brand msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Brand msg) = List_Brand (ListOf msg (Struct msg))

get_Brand'scopes :: ReadCtx m msg => Brand msg -> m (List msg (Brand'Scope msg)) Source #

has_Brand'scopes :: ReadCtx m msg => Brand msg -> m Bool Source #

set_Brand'scopes :: RWCtx m s => Brand (MutMsg s) -> List (MutMsg s) (Brand'Scope (MutMsg s)) -> m () Source #

newtype CapnpVersion msg Source #

Constructors

CapnpVersion_newtype_ (Struct msg) 
Instances
ToStruct msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: CapnpVersion msg -> Struct msg Source #

FromStruct msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (CapnpVersion msg) Source #

IsPtr msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (CapnpVersion msg) Source #

toPtr :: CapnpVersion msg -> Maybe (Ptr msg) Source #

Allocate s (CapnpVersion (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (CapnpVersion (MutMsg s)) Source #

MutListElem s (CapnpVersion (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => CapnpVersion (MutMsg s) -> Int -> List (MutMsg s) (CapnpVersion (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (CapnpVersion (MutMsg s))) Source #

ListElem msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (CapnpVersion msg) :: * Source #

Methods

length :: List msg (CapnpVersion msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (CapnpVersion msg) -> m (CapnpVersion msg) Source #

IsPtr msg (List msg (CapnpVersion msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (CapnpVersion msg)) Source #

toPtr :: List msg (CapnpVersion msg) -> Maybe (Ptr msg) Source #

MessageDefault (CapnpVersion msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> CapnpVersion msg Source #

HasMessage (CapnpVersion msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: CapnpVersion msg -> msg Source #

data List msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (CapnpVersion msg) = List_CapnpVersion (ListOf msg (Struct msg))

newtype CodeGeneratorRequest msg Source #

Instances
ToStruct msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (CodeGeneratorRequest msg) Source #

IsPtr msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (CodeGeneratorRequest msg) Source #

toPtr :: CodeGeneratorRequest msg -> Maybe (Ptr msg) Source #

Allocate s (CodeGeneratorRequest (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (CodeGeneratorRequest (MutMsg s)) Source #

MutListElem s (CodeGeneratorRequest (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (CodeGeneratorRequest msg) :: * Source #

Methods

length :: List msg (CodeGeneratorRequest msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (CodeGeneratorRequest msg) -> m (CodeGeneratorRequest msg) Source #

IsPtr msg (List msg (CodeGeneratorRequest msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (CodeGeneratorRequest msg)) Source #

toPtr :: List msg (CodeGeneratorRequest msg) -> Maybe (Ptr msg) Source #

MessageDefault (CodeGeneratorRequest msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (CodeGeneratorRequest msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: CodeGeneratorRequest msg -> msg Source #

data List msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data ElementSize Source #

Instances
Enum ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Eq ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Read ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Show ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Generic ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

type Rep ElementSize :: * -> * #

IsWord ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => ElementSize -> Int -> List (MutMsg s) ElementSize -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) ElementSize) Source #

ListElem msg ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg ElementSize :: * Source #

Methods

length :: List msg ElementSize -> Int Source #

index :: ReadCtx m msg => Int -> List msg ElementSize -> m ElementSize Source #

IsPtr msg (List msg ElementSize) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg ElementSize) Source #

toPtr :: List msg ElementSize -> Maybe (Ptr msg) Source #

type Rep ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

type Rep ElementSize = D1 (MetaData "ElementSize" "Capnp.Capnp.Schema" "capnp-0.2.0.0-GVlOuXtocAy6sjd7SXWbQY" False) (((C1 (MetaCons "ElementSize'empty" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ElementSize'bit" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "ElementSize'byte" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ElementSize'twoBytes" PrefixI False) (U1 :: * -> *))) :+: ((C1 (MetaCons "ElementSize'fourBytes" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ElementSize'eightBytes" PrefixI False) (U1 :: * -> *)) :+: (C1 (MetaCons "ElementSize'pointer" PrefixI False) (U1 :: * -> *) :+: (C1 (MetaCons "ElementSize'inlineComposite" PrefixI False) (U1 :: * -> *) :+: C1 (MetaCons "ElementSize'unknown'" PrefixI False) (S1 (MetaSel (Nothing :: Maybe Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 Word16))))))
data List msg ElementSize Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Enumerant msg Source #

Constructors

Enumerant_newtype_ (Struct msg) 
Instances
ToStruct msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Enumerant msg -> Struct msg Source #

FromStruct msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Enumerant msg) Source #

IsPtr msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Enumerant msg) Source #

toPtr :: Enumerant msg -> Maybe (Ptr msg) Source #

Allocate s (Enumerant (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Enumerant (MutMsg s)) Source #

MutListElem s (Enumerant (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Enumerant (MutMsg s) -> Int -> List (MutMsg s) (Enumerant (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Enumerant (MutMsg s))) Source #

ListElem msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Enumerant msg) :: * Source #

Methods

length :: List msg (Enumerant msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Enumerant msg) -> m (Enumerant msg) Source #

IsPtr msg (List msg (Enumerant msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Enumerant msg)) Source #

toPtr :: List msg (Enumerant msg) -> Maybe (Ptr msg) Source #

MessageDefault (Enumerant msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Enumerant msg Source #

HasMessage (Enumerant msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Enumerant msg -> msg Source #

data List msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Enumerant msg) = List_Enumerant (ListOf msg (Struct msg))

get_Enumerant'name :: ReadCtx m msg => Enumerant msg -> m (Text msg) Source #

newtype Field msg Source #

Constructors

Field_newtype_ (Struct msg) 
Instances
ToStruct msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Field msg -> Struct msg Source #

FromStruct msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field msg) Source #

IsPtr msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Field msg) Source #

toPtr :: Field msg -> Maybe (Ptr msg) Source #

Allocate s (Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field (MutMsg s)) Source #

MutListElem s (Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field (MutMsg s) -> Int -> List (MutMsg s) (Field (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field (MutMsg s))) Source #

ListElem msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field msg) :: * Source #

Methods

length :: List msg (Field msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field msg) -> m (Field msg) Source #

IsPtr msg (List msg (Field msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Field msg)) Source #

toPtr :: List msg (Field msg) -> Maybe (Ptr msg) Source #

MessageDefault (Field msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Field msg Source #

HasMessage (Field msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Field msg -> msg Source #

data List msg (Field msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Field msg) = List_Field (ListOf msg (Struct msg))

get_Field'name :: ReadCtx m msg => Field msg -> m (Text msg) Source #

has_Field'name :: ReadCtx m msg => Field msg -> m Bool Source #

set_Field'name :: RWCtx m s => Field (MutMsg s) -> Text (MutMsg s) -> m () Source #

new_Field'name :: RWCtx m s => Int -> Field (MutMsg s) -> m (Text (MutMsg s)) Source #

get_Field'annotations :: ReadCtx m msg => Field msg -> m (List msg (Annotation msg)) Source #

get_Field'union' :: ReadCtx m msg => Field msg -> m (Field' msg) Source #

has_Field'union' :: ReadCtx m msg => Field msg -> m Bool Source #

newtype Method msg Source #

Constructors

Method_newtype_ (Struct msg) 
Instances
ToStruct msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Method msg -> Struct msg Source #

FromStruct msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Method msg) Source #

IsPtr msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Method msg) Source #

toPtr :: Method msg -> Maybe (Ptr msg) Source #

Allocate s (Method (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Method (MutMsg s)) Source #

MutListElem s (Method (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Method (MutMsg s) -> Int -> List (MutMsg s) (Method (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Method (MutMsg s))) Source #

ListElem msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Method msg) :: * Source #

Methods

length :: List msg (Method msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Method msg) -> m (Method msg) Source #

IsPtr msg (List msg (Method msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Method msg)) Source #

toPtr :: List msg (Method msg) -> Maybe (Ptr msg) Source #

MessageDefault (Method msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Method msg Source #

HasMessage (Method msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Method msg -> msg Source #

data List msg (Method msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Method msg) = List_Method (ListOf msg (Struct msg))

get_Method'name :: ReadCtx m msg => Method msg -> m (Text msg) Source #

has_Method'name :: ReadCtx m msg => Method msg -> m Bool Source #

set_Method'name :: RWCtx m s => Method (MutMsg s) -> Text (MutMsg s) -> m () Source #

new_Method'name :: RWCtx m s => Int -> Method (MutMsg s) -> m (Text (MutMsg s)) Source #

get_Method'annotations :: ReadCtx m msg => Method msg -> m (List msg (Annotation msg)) Source #

get_Method'paramBrand :: ReadCtx m msg => Method msg -> m (Brand msg) Source #

get_Method'resultBrand :: ReadCtx m msg => Method msg -> m (Brand msg) Source #

newtype Node msg Source #

Constructors

Node_newtype_ (Struct msg) 
Instances
ToStruct msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node msg -> Struct msg Source #

FromStruct msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node msg) Source #

IsPtr msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Node msg) Source #

toPtr :: Node msg -> Maybe (Ptr msg) Source #

Allocate s (Node (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node (MutMsg s)) Source #

MutListElem s (Node (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node (MutMsg s) -> Int -> List (MutMsg s) (Node (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node (MutMsg s))) Source #

ListElem msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node msg) :: * Source #

Methods

length :: List msg (Node msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node msg) -> m (Node msg) Source #

IsPtr msg (List msg (Node msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node msg)) Source #

toPtr :: List msg (Node msg) -> Maybe (Ptr msg) Source #

MessageDefault (Node msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Node msg Source #

HasMessage (Node msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node msg -> msg Source #

data List msg (Node msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Node msg) = List_Node (ListOf msg (Struct msg))

get_Node'id :: ReadCtx m msg => Node msg -> m Word64 Source #

has_Node'id :: ReadCtx m msg => Node msg -> m Bool Source #

set_Node'id :: RWCtx m s => Node (MutMsg s) -> Word64 -> m () Source #

get_Node'displayName :: ReadCtx m msg => Node msg -> m (Text msg) Source #

set_Node'displayName :: RWCtx m s => Node (MutMsg s) -> Text (MutMsg s) -> m () Source #

has_Node'scopeId :: ReadCtx m msg => Node msg -> m Bool Source #

set_Node'scopeId :: RWCtx m s => Node (MutMsg s) -> Word64 -> m () Source #

get_Node'nestedNodes :: ReadCtx m msg => Node msg -> m (List msg (Node'NestedNode msg)) Source #

get_Node'annotations :: ReadCtx m msg => Node msg -> m (List msg (Annotation msg)) Source #

get_Node'parameters :: ReadCtx m msg => Node msg -> m (List msg (Node'Parameter msg)) Source #

set_Node'isGeneric :: RWCtx m s => Node (MutMsg s) -> Bool -> m () Source #

get_Node'union' :: ReadCtx m msg => Node msg -> m (Node' msg) Source #

has_Node'union' :: ReadCtx m msg => Node msg -> m Bool Source #

newtype Superclass msg Source #

Constructors

Superclass_newtype_ (Struct msg) 
Instances
ToStruct msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Superclass msg -> Struct msg Source #

FromStruct msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Superclass msg) Source #

IsPtr msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Superclass msg) Source #

toPtr :: Superclass msg -> Maybe (Ptr msg) Source #

Allocate s (Superclass (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Superclass (MutMsg s)) Source #

MutListElem s (Superclass (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Superclass (MutMsg s) -> Int -> List (MutMsg s) (Superclass (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Superclass (MutMsg s))) Source #

ListElem msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Superclass msg) :: * Source #

Methods

length :: List msg (Superclass msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Superclass msg) -> m (Superclass msg) Source #

IsPtr msg (List msg (Superclass msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Superclass msg)) Source #

toPtr :: List msg (Superclass msg) -> Maybe (Ptr msg) Source #

MessageDefault (Superclass msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Superclass msg Source #

HasMessage (Superclass msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Superclass msg -> msg Source #

data List msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Superclass msg) = List_Superclass (ListOf msg (Struct msg))

newtype Type msg Source #

Constructors

Type_newtype_ (Struct msg) 
Instances
ToStruct msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Type msg -> Struct msg Source #

FromStruct msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type msg) Source #

IsPtr msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Type msg) Source #

toPtr :: Type msg -> Maybe (Ptr msg) Source #

Allocate s (Type (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type (MutMsg s)) Source #

MutListElem s (Type (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type (MutMsg s) -> Int -> List (MutMsg s) (Type (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type (MutMsg s))) Source #

ListElem msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type msg) :: * Source #

Methods

length :: List msg (Type msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type msg) -> m (Type msg) Source #

IsPtr msg (List msg (Type msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type msg)) Source #

toPtr :: List msg (Type msg) -> Maybe (Ptr msg) Source #

MessageDefault (Type msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Type msg Source #

HasMessage (Type msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Type msg -> msg Source #

data List msg (Type msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Type msg) = List_Type (ListOf msg (Struct msg))

get_Type' :: ReadCtx m msg => Type msg -> m (Type' msg) Source #

has_Type' :: ReadCtx m msg => Type msg -> m Bool Source #

set_Type'void :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'bool :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'int8 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'int16 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'int32 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'int64 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'uint8 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'uint16 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'uint32 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'uint64 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'float32 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'float64 :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'text :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'data_ :: RWCtx m s => Type (MutMsg s) -> m () Source #

set_Type'unknown' :: RWCtx m s => Type (MutMsg s) -> Word16 -> m () Source #

newtype Type'list'group' msg Source #

Constructors

Type'list'group'_newtype_ (Struct msg) 
Instances
ToStruct msg (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Type'list'group' msg -> Struct msg Source #

FromStruct msg (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'list'group' msg) Source #

IsPtr msg (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Type'list'group' msg) Source #

toPtr :: Type'list'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Type'list'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'list'group' (MutMsg s)) Source #

MutListElem s (Type'list'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type'list'group' (MutMsg s) -> Int -> List (MutMsg s) (Type'list'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type'list'group' (MutMsg s))) Source #

ListElem msg (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'list'group' msg) :: * Source #

Methods

length :: List msg (Type'list'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type'list'group' msg) -> m (Type'list'group' msg) Source #

IsPtr msg (List msg (Type'list'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type'list'group' msg)) Source #

toPtr :: List msg (Type'list'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Type'list'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'list'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Type'list'group' msg -> msg Source #

data List msg (Type'list'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Type'enum'group' msg Source #

Constructors

Type'enum'group'_newtype_ (Struct msg) 
Instances
ToStruct msg (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Type'enum'group' msg -> Struct msg Source #

FromStruct msg (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'enum'group' msg) Source #

IsPtr msg (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Type'enum'group' msg) Source #

toPtr :: Type'enum'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Type'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'enum'group' (MutMsg s)) Source #

MutListElem s (Type'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type'enum'group' (MutMsg s) -> Int -> List (MutMsg s) (Type'enum'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type'enum'group' (MutMsg s))) Source #

ListElem msg (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'enum'group' msg) :: * Source #

Methods

length :: List msg (Type'enum'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type'enum'group' msg) -> m (Type'enum'group' msg) Source #

IsPtr msg (List msg (Type'enum'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type'enum'group' msg)) Source #

toPtr :: List msg (Type'enum'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Type'enum'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'enum'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Type'enum'group' msg -> msg Source #

data List msg (Type'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Type'struct'group' msg Source #

Instances
ToStruct msg (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'struct'group' msg) Source #

IsPtr msg (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Type'struct'group' msg) Source #

toPtr :: Type'struct'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Type'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'struct'group' (MutMsg s)) Source #

MutListElem s (Type'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'struct'group' msg) :: * Source #

Methods

length :: List msg (Type'struct'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type'struct'group' msg) -> m (Type'struct'group' msg) Source #

IsPtr msg (List msg (Type'struct'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type'struct'group' msg)) Source #

toPtr :: List msg (Type'struct'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Type'struct'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'struct'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Type'struct'group' msg -> msg Source #

data List msg (Type'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Type'interface'group' msg Source #

Instances
ToStruct msg (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'interface'group' msg) Source #

IsPtr msg (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Type'interface'group' msg) Source #

toPtr :: Type'interface'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Type'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'interface'group' (MutMsg s)) Source #

MutListElem s (Type'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'interface'group' msg) :: * Source #

IsPtr msg (List msg (Type'interface'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type'interface'group' msg)) Source #

toPtr :: List msg (Type'interface'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Type'interface'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'interface'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Type'interface'group' msg -> msg Source #

data List msg (Type'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Type'anyPointer'group' msg Source #

Instances
ToStruct msg (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'anyPointer'group' msg) Source #

IsPtr msg (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Type'anyPointer'group' msg) Source #

toPtr :: Type'anyPointer'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Type'anyPointer'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'anyPointer'group' (MutMsg s)) Source #

MutListElem s (Type'anyPointer'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer'group' msg) :: * Source #

IsPtr msg (List msg (Type'anyPointer'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type'anyPointer'group' msg)) Source #

toPtr :: List msg (Type'anyPointer'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Type'anyPointer'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'anyPointer'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Type'anyPointer'group' msg -> msg Source #

data List msg (Type'anyPointer'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Value msg Source #

Constructors

Value_newtype_ (Struct msg) 
Instances
ToStruct msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Value msg -> Struct msg Source #

FromStruct msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Value msg) Source #

IsPtr msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Value msg) Source #

toPtr :: Value msg -> Maybe (Ptr msg) Source #

Allocate s (Value (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Value (MutMsg s)) Source #

MutListElem s (Value (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Value (MutMsg s) -> Int -> List (MutMsg s) (Value (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Value (MutMsg s))) Source #

ListElem msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Value msg) :: * Source #

Methods

length :: List msg (Value msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Value msg) -> m (Value msg) Source #

IsPtr msg (List msg (Value msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Value msg)) Source #

toPtr :: List msg (Value msg) -> Maybe (Ptr msg) Source #

MessageDefault (Value msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Value msg Source #

HasMessage (Value msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Value msg -> msg Source #

data List msg (Value msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Value msg) = List_Value (ListOf msg (Struct msg))

get_Value' :: ReadCtx m msg => Value msg -> m (Value' msg) Source #

has_Value' :: ReadCtx m msg => Value msg -> m Bool Source #

set_Value'void :: RWCtx m s => Value (MutMsg s) -> m () Source #

set_Value'bool :: RWCtx m s => Value (MutMsg s) -> Bool -> m () Source #

set_Value'int8 :: RWCtx m s => Value (MutMsg s) -> Int8 -> m () Source #

set_Value'int16 :: RWCtx m s => Value (MutMsg s) -> Int16 -> m () Source #

set_Value'int32 :: RWCtx m s => Value (MutMsg s) -> Int32 -> m () Source #

set_Value'int64 :: RWCtx m s => Value (MutMsg s) -> Int64 -> m () Source #

set_Value'uint8 :: RWCtx m s => Value (MutMsg s) -> Word8 -> m () Source #

set_Value'uint16 :: RWCtx m s => Value (MutMsg s) -> Word16 -> m () Source #

set_Value'uint32 :: RWCtx m s => Value (MutMsg s) -> Word32 -> m () Source #

set_Value'uint64 :: RWCtx m s => Value (MutMsg s) -> Word64 -> m () Source #

set_Value'float32 :: RWCtx m s => Value (MutMsg s) -> Float -> m () Source #

set_Value'float64 :: RWCtx m s => Value (MutMsg s) -> Double -> m () Source #

set_Value'text :: RWCtx m s => Value (MutMsg s) -> Text (MutMsg s) -> m () Source #

new_Value'text :: RWCtx m s => Int -> Value (MutMsg s) -> m (Text (MutMsg s)) Source #

set_Value'data_ :: RWCtx m s => Value (MutMsg s) -> Data (MutMsg s) -> m () Source #

new_Value'data_ :: RWCtx m s => Int -> Value (MutMsg s) -> m (Data (MutMsg s)) Source #

set_Value'list :: RWCtx m s => Value (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #

set_Value'enum :: RWCtx m s => Value (MutMsg s) -> Word16 -> m () Source #

set_Value'struct :: RWCtx m s => Value (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #

set_Value'anyPointer :: RWCtx m s => Value (MutMsg s) -> Maybe (Ptr (MutMsg s)) -> m () Source #

newtype Brand'Binding msg Source #

Constructors

Brand'Binding_newtype_ (Struct msg) 
Instances
ToStruct msg (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Brand'Binding msg -> Struct msg Source #

FromStruct msg (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Binding msg) Source #

IsPtr msg (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Brand'Binding msg) Source #

toPtr :: Brand'Binding msg -> Maybe (Ptr msg) Source #

Allocate s (Brand'Binding (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Brand'Binding (MutMsg s)) Source #

MutListElem s (Brand'Binding (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand'Binding (MutMsg s) -> Int -> List (MutMsg s) (Brand'Binding (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand'Binding (MutMsg s))) Source #

ListElem msg (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Brand'Binding msg) :: * Source #

Methods

length :: List msg (Brand'Binding msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Brand'Binding msg) -> m (Brand'Binding msg) Source #

IsPtr msg (List msg (Brand'Binding msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Brand'Binding msg)) Source #

toPtr :: List msg (Brand'Binding msg) -> Maybe (Ptr msg) Source #

MessageDefault (Brand'Binding msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Brand'Binding msg Source #

HasMessage (Brand'Binding msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Brand'Binding msg -> msg Source #

data List msg (Brand'Binding msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Brand'Binding msg) = List_Brand'Binding (ListOf msg (Struct msg))

data Brand'Binding' msg Source #

Instances
FromStruct msg (Brand'Binding' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Binding' msg) Source #

newtype Brand'Scope msg Source #

Constructors

Brand'Scope_newtype_ (Struct msg) 
Instances
ToStruct msg (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Brand'Scope msg -> Struct msg Source #

FromStruct msg (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Scope msg) Source #

IsPtr msg (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Brand'Scope msg) Source #

toPtr :: Brand'Scope msg -> Maybe (Ptr msg) Source #

Allocate s (Brand'Scope (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Brand'Scope (MutMsg s)) Source #

MutListElem s (Brand'Scope (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand'Scope (MutMsg s) -> Int -> List (MutMsg s) (Brand'Scope (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand'Scope (MutMsg s))) Source #

ListElem msg (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Brand'Scope msg) :: * Source #

Methods

length :: List msg (Brand'Scope msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Brand'Scope msg) -> m (Brand'Scope msg) Source #

IsPtr msg (List msg (Brand'Scope msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Brand'Scope msg)) Source #

toPtr :: List msg (Brand'Scope msg) -> Maybe (Ptr msg) Source #

MessageDefault (Brand'Scope msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Brand'Scope msg Source #

HasMessage (Brand'Scope msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Brand'Scope msg -> msg Source #

data List msg (Brand'Scope msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Brand'Scope msg) = List_Brand'Scope (ListOf msg (Struct msg))

newtype Brand'Scope' msg Source #

Constructors

Brand'Scope'_newtype_ (Struct msg) 
Instances
ToStruct msg (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Brand'Scope' msg -> Struct msg Source #

FromStruct msg (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Scope' msg) Source #

IsPtr msg (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Brand'Scope' msg) Source #

toPtr :: Brand'Scope' msg -> Maybe (Ptr msg) Source #

Allocate s (Brand'Scope' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Brand'Scope' (MutMsg s)) Source #

MutListElem s (Brand'Scope' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Brand'Scope' (MutMsg s) -> Int -> List (MutMsg s) (Brand'Scope' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Brand'Scope' (MutMsg s))) Source #

ListElem msg (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Brand'Scope' msg) :: * Source #

Methods

length :: List msg (Brand'Scope' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Brand'Scope' msg) -> m (Brand'Scope' msg) Source #

IsPtr msg (List msg (Brand'Scope' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Brand'Scope' msg)) Source #

toPtr :: List msg (Brand'Scope' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Brand'Scope' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Brand'Scope' msg Source #

HasMessage (Brand'Scope' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Brand'Scope' msg -> msg Source #

data List msg (Brand'Scope' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Brand'Scope' msg) = List_Brand'Scope' (ListOf msg (Struct msg))

data Brand'Scope'' msg Source #

Instances
FromStruct msg (Brand'Scope'' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Brand'Scope'' msg) Source #

newtype CodeGeneratorRequest'RequestedFile msg Source #

Instances
ToStruct msg (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

IsPtr msg (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (CodeGeneratorRequest'RequestedFile (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (CodeGeneratorRequest'RequestedFile (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (CodeGeneratorRequest'RequestedFile msg) :: * Source #

IsPtr msg (List msg (CodeGeneratorRequest'RequestedFile msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (CodeGeneratorRequest'RequestedFile msg)) Source #

toPtr :: List msg (CodeGeneratorRequest'RequestedFile msg) -> Maybe (Ptr msg) Source #

MessageDefault (CodeGeneratorRequest'RequestedFile msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (CodeGeneratorRequest'RequestedFile msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (CodeGeneratorRequest'RequestedFile msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype CodeGeneratorRequest'RequestedFile'Import msg Source #

Instances
ToStruct msg (CodeGeneratorRequest'RequestedFile'Import msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (CodeGeneratorRequest'RequestedFile'Import msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

IsPtr msg (CodeGeneratorRequest'RequestedFile'Import msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (CodeGeneratorRequest'RequestedFile'Import (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (CodeGeneratorRequest'RequestedFile'Import (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (CodeGeneratorRequest'RequestedFile'Import msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (CodeGeneratorRequest'RequestedFile'Import msg) :: * Source #

IsPtr msg (List msg (CodeGeneratorRequest'RequestedFile'Import msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (CodeGeneratorRequest'RequestedFile'Import msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (CodeGeneratorRequest'RequestedFile'Import msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (CodeGeneratorRequest'RequestedFile'Import msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Field' msg Source #

Constructors

Field'_newtype_ (Struct msg) 
Instances
ToStruct msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Field' msg -> Struct msg Source #

FromStruct msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field' msg) Source #

IsPtr msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Field' msg) Source #

toPtr :: Field' msg -> Maybe (Ptr msg) Source #

Allocate s (Field' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field' (MutMsg s)) Source #

MutListElem s (Field' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field' (MutMsg s) -> Int -> List (MutMsg s) (Field' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field' (MutMsg s))) Source #

ListElem msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field' msg) :: * Source #

Methods

length :: List msg (Field' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field' msg) -> m (Field' msg) Source #

IsPtr msg (List msg (Field' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Field' msg)) Source #

toPtr :: List msg (Field' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Field' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Field' msg Source #

HasMessage (Field' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Field' msg -> msg Source #

data List msg (Field' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Field' msg) = List_Field' (ListOf msg (Struct msg))

data Field'' msg Source #

Instances
FromStruct msg (Field'' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field'' msg) Source #

get_Field'' :: ReadCtx m msg => Field' msg -> m (Field'' msg) Source #

has_Field'' :: ReadCtx m msg => Field' msg -> m Bool Source #

newtype Field'slot'group' msg Source #

Instances
ToStruct msg (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field'slot'group' msg) Source #

IsPtr msg (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Field'slot'group' msg) Source #

toPtr :: Field'slot'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Field'slot'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field'slot'group' (MutMsg s)) Source #

MutListElem s (Field'slot'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field'slot'group' (MutMsg s) -> Int -> List (MutMsg s) (Field'slot'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field'slot'group' (MutMsg s))) Source #

ListElem msg (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field'slot'group' msg) :: * Source #

Methods

length :: List msg (Field'slot'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field'slot'group' msg) -> m (Field'slot'group' msg) Source #

IsPtr msg (List msg (Field'slot'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Field'slot'group' msg)) Source #

toPtr :: List msg (Field'slot'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Field'slot'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Field'slot'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Field'slot'group' msg -> msg Source #

data List msg (Field'slot'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Field'group'group' msg Source #

Instances
ToStruct msg (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field'group'group' msg) Source #

IsPtr msg (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Field'group'group' msg) Source #

toPtr :: Field'group'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Field'group'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field'group'group' (MutMsg s)) Source #

MutListElem s (Field'group'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field'group'group' msg) :: * Source #

Methods

length :: List msg (Field'group'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field'group'group' msg) -> m (Field'group'group' msg) Source #

IsPtr msg (List msg (Field'group'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Field'group'group' msg)) Source #

toPtr :: List msg (Field'group'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Field'group'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Field'group'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Field'group'group' msg -> msg Source #

data List msg (Field'group'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Field'ordinal msg Source #

Constructors

Field'ordinal_newtype_ (Struct msg) 
Instances
ToStruct msg (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Field'ordinal msg -> Struct msg Source #

FromStruct msg (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Field'ordinal msg) Source #

IsPtr msg (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Field'ordinal msg) Source #

toPtr :: Field'ordinal msg -> Maybe (Ptr msg) Source #

Allocate s (Field'ordinal (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Field'ordinal (MutMsg s)) Source #

MutListElem s (Field'ordinal (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Field'ordinal (MutMsg s) -> Int -> List (MutMsg s) (Field'ordinal (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Field'ordinal (MutMsg s))) Source #

ListElem msg (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Field'ordinal msg) :: * Source #

Methods

length :: List msg (Field'ordinal msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Field'ordinal msg) -> m (Field'ordinal msg) Source #

IsPtr msg (List msg (Field'ordinal msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Field'ordinal msg)) Source #

toPtr :: List msg (Field'ordinal msg) -> Maybe (Ptr msg) Source #

MessageDefault (Field'ordinal msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Field'ordinal msg Source #

HasMessage (Field'ordinal msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Field'ordinal msg -> msg Source #

data List msg (Field'ordinal msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Field'ordinal msg) = List_Field'ordinal (ListOf msg (Struct msg))

newtype Node' msg Source #

Constructors

Node'_newtype_ (Struct msg) 
Instances
ToStruct msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node' msg -> Struct msg Source #

FromStruct msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node' msg) Source #

IsPtr msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Node' msg) Source #

toPtr :: Node' msg -> Maybe (Ptr msg) Source #

Allocate s (Node' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node' (MutMsg s)) Source #

MutListElem s (Node' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node' (MutMsg s) -> Int -> List (MutMsg s) (Node' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node' (MutMsg s))) Source #

ListElem msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node' msg) :: * Source #

Methods

length :: List msg (Node' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node' msg) -> m (Node' msg) Source #

IsPtr msg (List msg (Node' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node' msg)) Source #

toPtr :: List msg (Node' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Node' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Node' msg Source #

HasMessage (Node' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node' msg -> msg Source #

data List msg (Node' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Node' msg) = List_Node' (ListOf msg (Struct msg))

get_Node'' :: ReadCtx m msg => Node' msg -> m (Node'' msg) Source #

has_Node'' :: ReadCtx m msg => Node' msg -> m Bool Source #

set_Node'file :: RWCtx m s => Node' (MutMsg s) -> m () Source #

set_Node'unknown' :: RWCtx m s => Node' (MutMsg s) -> Word16 -> m () Source #

newtype Node'struct'group' msg Source #

Instances
ToStruct msg (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'struct'group' msg) Source #

IsPtr msg (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Node'struct'group' msg) Source #

toPtr :: Node'struct'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Node'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'struct'group' (MutMsg s)) Source #

MutListElem s (Node'struct'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'struct'group' msg) :: * Source #

Methods

length :: List msg (Node'struct'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'struct'group' msg) -> m (Node'struct'group' msg) Source #

IsPtr msg (List msg (Node'struct'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'struct'group' msg)) Source #

toPtr :: List msg (Node'struct'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Node'struct'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Node'struct'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node'struct'group' msg -> msg Source #

data List msg (Node'struct'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Node'enum'group' msg Source #

Constructors

Node'enum'group'_newtype_ (Struct msg) 
Instances
ToStruct msg (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node'enum'group' msg -> Struct msg Source #

FromStruct msg (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'enum'group' msg) Source #

IsPtr msg (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Node'enum'group' msg) Source #

toPtr :: Node'enum'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Node'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'enum'group' (MutMsg s)) Source #

MutListElem s (Node'enum'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'enum'group' (MutMsg s) -> Int -> List (MutMsg s) (Node'enum'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'enum'group' (MutMsg s))) Source #

ListElem msg (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'enum'group' msg) :: * Source #

Methods

length :: List msg (Node'enum'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'enum'group' msg) -> m (Node'enum'group' msg) Source #

IsPtr msg (List msg (Node'enum'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'enum'group' msg)) Source #

toPtr :: List msg (Node'enum'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Node'enum'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Node'enum'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node'enum'group' msg -> msg Source #

data List msg (Node'enum'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Node'interface'group' msg Source #

Instances
ToStruct msg (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'interface'group' msg) Source #

IsPtr msg (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Node'interface'group' msg) Source #

toPtr :: Node'interface'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Node'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'interface'group' (MutMsg s)) Source #

MutListElem s (Node'interface'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'interface'group' msg) :: * Source #

IsPtr msg (List msg (Node'interface'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'interface'group' msg)) Source #

toPtr :: List msg (Node'interface'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Node'interface'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Node'interface'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node'interface'group' msg -> msg Source #

data List msg (Node'interface'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Node'const'group' msg Source #

Instances
ToStruct msg (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'const'group' msg) Source #

IsPtr msg (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Node'const'group' msg) Source #

toPtr :: Node'const'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Node'const'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'const'group' (MutMsg s)) Source #

MutListElem s (Node'const'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'const'group' (MutMsg s) -> Int -> List (MutMsg s) (Node'const'group' (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'const'group' (MutMsg s))) Source #

ListElem msg (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'const'group' msg) :: * Source #

Methods

length :: List msg (Node'const'group' msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'const'group' msg) -> m (Node'const'group' msg) Source #

IsPtr msg (List msg (Node'const'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'const'group' msg)) Source #

toPtr :: List msg (Node'const'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Node'const'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Node'const'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node'const'group' msg -> msg Source #

data List msg (Node'const'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Node'annotation'group' msg Source #

Instances
ToStruct msg (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'annotation'group' msg) Source #

IsPtr msg (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Node'annotation'group' msg) Source #

toPtr :: Node'annotation'group' msg -> Maybe (Ptr msg) Source #

Allocate s (Node'annotation'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'annotation'group' (MutMsg s)) Source #

MutListElem s (Node'annotation'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'annotation'group' msg) :: * Source #

IsPtr msg (List msg (Node'annotation'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'annotation'group' msg)) Source #

toPtr :: List msg (Node'annotation'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Node'annotation'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Node'annotation'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node'annotation'group' msg -> msg Source #

data List msg (Node'annotation'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Node'NestedNode msg Source #

Constructors

Node'NestedNode_newtype_ (Struct msg) 
Instances
ToStruct msg (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node'NestedNode msg -> Struct msg Source #

FromStruct msg (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'NestedNode msg) Source #

IsPtr msg (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Node'NestedNode msg) Source #

toPtr :: Node'NestedNode msg -> Maybe (Ptr msg) Source #

Allocate s (Node'NestedNode (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'NestedNode (MutMsg s)) Source #

MutListElem s (Node'NestedNode (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'NestedNode (MutMsg s) -> Int -> List (MutMsg s) (Node'NestedNode (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'NestedNode (MutMsg s))) Source #

ListElem msg (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'NestedNode msg) :: * Source #

Methods

length :: List msg (Node'NestedNode msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'NestedNode msg) -> m (Node'NestedNode msg) Source #

IsPtr msg (List msg (Node'NestedNode msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'NestedNode msg)) Source #

toPtr :: List msg (Node'NestedNode msg) -> Maybe (Ptr msg) Source #

MessageDefault (Node'NestedNode msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Node'NestedNode msg Source #

HasMessage (Node'NestedNode msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node'NestedNode msg -> msg Source #

data List msg (Node'NestedNode msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Node'Parameter msg Source #

Constructors

Node'Parameter_newtype_ (Struct msg) 
Instances
ToStruct msg (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Node'Parameter msg -> Struct msg Source #

FromStruct msg (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Node'Parameter msg) Source #

IsPtr msg (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Node'Parameter msg) Source #

toPtr :: Node'Parameter msg -> Maybe (Ptr msg) Source #

Allocate s (Node'Parameter (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Node'Parameter (MutMsg s)) Source #

MutListElem s (Node'Parameter (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Node'Parameter (MutMsg s) -> Int -> List (MutMsg s) (Node'Parameter (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Node'Parameter (MutMsg s))) Source #

ListElem msg (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Node'Parameter msg) :: * Source #

Methods

length :: List msg (Node'Parameter msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Node'Parameter msg) -> m (Node'Parameter msg) Source #

IsPtr msg (List msg (Node'Parameter msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Node'Parameter msg)) Source #

toPtr :: List msg (Node'Parameter msg) -> Maybe (Ptr msg) Source #

MessageDefault (Node'Parameter msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Node'Parameter msg Source #

HasMessage (Node'Parameter msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Node'Parameter msg -> msg Source #

data List msg (Node'Parameter msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Node'Parameter msg) = List_Node'Parameter (ListOf msg (Struct msg))

newtype Type'anyPointer msg Source #

Constructors

Type'anyPointer_newtype_ (Struct msg) 
Instances
ToStruct msg (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

toStruct :: Type'anyPointer msg -> Struct msg Source #

FromStruct msg (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromStruct :: ReadCtx m msg => Struct msg -> m (Type'anyPointer msg) Source #

IsPtr msg (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (Type'anyPointer msg) Source #

toPtr :: Type'anyPointer msg -> Maybe (Ptr msg) Source #

Allocate s (Type'anyPointer (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

new :: WriteCtx m s => MutMsg s -> m (Type'anyPointer (MutMsg s)) Source #

MutListElem s (Type'anyPointer (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

setIndex :: RWCtx m s => Type'anyPointer (MutMsg s) -> Int -> List (MutMsg s) (Type'anyPointer (MutMsg s)) -> m () Source #

newList :: WriteCtx m s => MutMsg s -> Int -> m (List (MutMsg s) (Type'anyPointer (MutMsg s))) Source #

ListElem msg (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer msg) :: * Source #

Methods

length :: List msg (Type'anyPointer msg) -> Int Source #

index :: ReadCtx m msg => Int -> List msg (Type'anyPointer msg) -> m (Type'anyPointer msg) Source #

IsPtr msg (List msg (Type'anyPointer msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type'anyPointer msg)) Source #

toPtr :: List msg (Type'anyPointer msg) -> Maybe (Ptr msg) Source #

MessageDefault (Type'anyPointer msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

messageDefault :: msg -> Type'anyPointer msg Source #

HasMessage (Type'anyPointer msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

message :: Type'anyPointer msg -> msg Source #

data List msg (Type'anyPointer msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Type'anyPointer'unconstrained'group' msg Source #

Instances
ToStruct msg (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

IsPtr msg (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (Type'anyPointer'unconstrained'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'unconstrained'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer'unconstrained'group' msg) :: * Source #

IsPtr msg (List msg (Type'anyPointer'unconstrained'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'anyPointer'unconstrained'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'anyPointer'unconstrained'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Type'anyPointer'unconstrained'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Type'anyPointer'parameter'group' msg Source #

Instances
ToStruct msg (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

IsPtr msg (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (Type'anyPointer'parameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'parameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer'parameter'group' msg) :: * Source #

IsPtr msg (List msg (Type'anyPointer'parameter'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type'anyPointer'parameter'group' msg)) Source #

toPtr :: List msg (Type'anyPointer'parameter'group' msg) -> Maybe (Ptr msg) Source #

MessageDefault (Type'anyPointer'parameter'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'anyPointer'parameter'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Type'anyPointer'parameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Type'anyPointer'implicitMethodParameter'group' msg Source #

Instances
ToStruct msg (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

IsPtr msg (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (Type'anyPointer'implicitMethodParameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'implicitMethodParameter'group' (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

IsPtr msg (List msg (Type'anyPointer'implicitMethodParameter'group' msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MessageDefault (Type'anyPointer'implicitMethodParameter'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'anyPointer'implicitMethodParameter'group' msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Type'anyPointer'implicitMethodParameter'group' msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

newtype Type'anyPointer'unconstrained msg Source #

Instances
ToStruct msg (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

FromStruct msg (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

IsPtr msg (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Allocate s (Type'anyPointer'unconstrained (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

MutListElem s (Type'anyPointer'unconstrained (MutMsg s)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

ListElem msg (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Associated Types

data List msg (Type'anyPointer'unconstrained msg) :: * Source #

IsPtr msg (List msg (Type'anyPointer'unconstrained msg)) Source # 
Instance details

Defined in Capnp.Capnp.Schema

Methods

fromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Type'anyPointer'unconstrained msg)) Source #

toPtr :: List msg (Type'anyPointer'unconstrained msg) -> Maybe (Ptr msg) Source #

MessageDefault (Type'anyPointer'unconstrained msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

HasMessage (Type'anyPointer'unconstrained msg) msg Source # 
Instance details

Defined in Capnp.Capnp.Schema

data List msg (Type'anyPointer'unconstrained msg) Source # 
Instance details

Defined in Capnp.Capnp.Schema