Safe Haskell | None |
---|---|
Language | Haskell2010 |
Documentation
Node'newtype_ (Struct msg) |
Instances
ToStruct msg (Node msg) Source # | |
FromStruct msg (Node msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
ToPtr s (Node ('Mut s)) Source # | |
FromPtr msg (Node msg) Source # | |
Allocate s (Node ('Mut s)) Source # | |
MutListElem s (Node ('Mut s)) Source # | |
ListElem mut (Node mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
MessageDefault (Node mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Node mut) mut Source # | |
newtype List mut (Node mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
get_Node'displayName :: (ReadCtx m msg, FromPtr msg (Text msg)) => Node msg -> m (Text msg) Source #
set_Node'displayName :: (RWCtx m s, ToPtr s (Text (Mut s))) => Node (Mut s) -> Text (Mut s) -> m () Source #
get_Node'nestedNodes :: (ReadCtx m msg, FromPtr msg (List msg (Node'NestedNode msg))) => Node msg -> m (List msg (Node'NestedNode msg)) Source #
set_Node'nestedNodes :: (RWCtx m s, ToPtr s (List (Mut s) (Node'NestedNode (Mut s)))) => Node (Mut s) -> List (Mut s) (Node'NestedNode (Mut s)) -> m () Source #
new_Node'nestedNodes :: RWCtx m s => Int -> Node (Mut s) -> m (List (Mut s) (Node'NestedNode (Mut s))) Source #
get_Node'annotations :: (ReadCtx m msg, FromPtr msg (List msg (Annotation msg))) => Node msg -> m (List msg (Annotation msg)) Source #
set_Node'annotations :: (RWCtx m s, ToPtr s (List (Mut s) (Annotation (Mut s)))) => Node (Mut s) -> List (Mut s) (Annotation (Mut s)) -> m () Source #
new_Node'annotations :: RWCtx m s => Int -> Node (Mut s) -> m (List (Mut s) (Annotation (Mut s))) Source #
get_Node'parameters :: (ReadCtx m msg, FromPtr msg (List msg (Node'Parameter msg))) => Node msg -> m (List msg (Node'Parameter msg)) Source #
set_Node'parameters :: (RWCtx m s, ToPtr s (List (Mut s) (Node'Parameter (Mut s)))) => Node (Mut s) -> List (Mut s) (Node'Parameter (Mut s)) -> m () Source #
new_Node'parameters :: RWCtx m s => Int -> Node (Mut s) -> m (List (Mut s) (Node'Parameter (Mut s))) Source #
data Node' (mut :: Mutability) Source #
Node'file | |
Node'struct (Node'struct mut) | |
Node'enum (Node'enum mut) | |
Node'interface (Node'interface mut) | |
Node'const (Node'const mut) | |
Node'annotation (Node'annotation mut) | |
Node'unknown' Word16 |
Instances
FromStruct mut (Node' mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
set_Node'struct :: (RWCtx m s, FromStruct (Mut s) (Node'struct (Mut s))) => Node (Mut s) -> m (Node'struct (Mut s)) Source #
set_Node'enum :: (RWCtx m s, FromStruct (Mut s) (Node'enum (Mut s))) => Node (Mut s) -> m (Node'enum (Mut s)) Source #
set_Node'interface :: (RWCtx m s, FromStruct (Mut s) (Node'interface (Mut s))) => Node (Mut s) -> m (Node'interface (Mut s)) Source #
set_Node'const :: (RWCtx m s, FromStruct (Mut s) (Node'const (Mut s))) => Node (Mut s) -> m (Node'const (Mut s)) Source #
set_Node'annotation :: (RWCtx m s, FromStruct (Mut s) (Node'annotation (Mut s))) => Node (Mut s) -> m (Node'annotation (Mut s)) Source #
newtype Node'struct msg Source #
Node'struct'newtype_ (Struct msg) |
Instances
ToStruct msg (Node'struct msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Node'struct msg -> Struct msg Source # | |
FromStruct msg (Node'struct msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Node'struct msg) Source # | |
MessageDefault (Node'struct mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Node'struct mut) Source # | |
HasMessage (Node'struct mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Node'struct mut -> Message mut Source # |
get_Node'struct'dataWordCount :: ReadCtx m msg => Node'struct msg -> m Word16 Source #
set_Node'struct'dataWordCount :: RWCtx m s => Node'struct (Mut s) -> Word16 -> m () Source #
get_Node'struct'pointerCount :: ReadCtx m msg => Node'struct msg -> m Word16 Source #
set_Node'struct'pointerCount :: RWCtx m s => Node'struct (Mut s) -> Word16 -> m () Source #
get_Node'struct'preferredListEncoding :: ReadCtx m msg => Node'struct msg -> m ElementSize Source #
set_Node'struct'preferredListEncoding :: RWCtx m s => Node'struct (Mut s) -> ElementSize -> m () Source #
get_Node'struct'isGroup :: ReadCtx m msg => Node'struct msg -> m Bool Source #
set_Node'struct'isGroup :: RWCtx m s => Node'struct (Mut s) -> Bool -> m () Source #
get_Node'struct'discriminantCount :: ReadCtx m msg => Node'struct msg -> m Word16 Source #
set_Node'struct'discriminantCount :: RWCtx m s => Node'struct (Mut s) -> Word16 -> m () Source #
get_Node'struct'discriminantOffset :: ReadCtx m msg => Node'struct msg -> m Word32 Source #
set_Node'struct'discriminantOffset :: RWCtx m s => Node'struct (Mut s) -> Word32 -> m () Source #
get_Node'struct'fields :: (ReadCtx m msg, FromPtr msg (List msg (Field msg))) => Node'struct msg -> m (List msg (Field msg)) Source #
set_Node'struct'fields :: (RWCtx m s, ToPtr s (List (Mut s) (Field (Mut s)))) => Node'struct (Mut s) -> List (Mut s) (Field (Mut s)) -> m () Source #
has_Node'struct'fields :: ReadCtx m msg => Node'struct msg -> m Bool Source #
new_Node'struct'fields :: RWCtx m s => Int -> Node'struct (Mut s) -> m (List (Mut s) (Field (Mut s))) Source #
newtype Node'enum msg Source #
Node'enum'newtype_ (Struct msg) |
Instances
ToStruct msg (Node'enum msg) Source # | |
FromStruct msg (Node'enum msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
MessageDefault (Node'enum mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Node'enum mut) mut Source # | |
get_Node'enum'enumerants :: (ReadCtx m msg, FromPtr msg (List msg (Enumerant msg))) => Node'enum msg -> m (List msg (Enumerant msg)) Source #
set_Node'enum'enumerants :: (RWCtx m s, ToPtr s (List (Mut s) (Enumerant (Mut s)))) => Node'enum (Mut s) -> List (Mut s) (Enumerant (Mut s)) -> m () Source #
new_Node'enum'enumerants :: RWCtx m s => Int -> Node'enum (Mut s) -> m (List (Mut s) (Enumerant (Mut s))) Source #
newtype Node'interface msg Source #
Instances
ToStruct msg (Node'interface msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Node'interface msg -> Struct msg Source # | |
FromStruct msg (Node'interface msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Node'interface msg) Source # | |
MessageDefault (Node'interface mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Node'interface mut) Source # | |
HasMessage (Node'interface mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Node'interface mut -> Message mut Source # |
get_Node'interface'methods :: (ReadCtx m msg, FromPtr msg (List msg (Method msg))) => Node'interface msg -> m (List msg (Method msg)) Source #
set_Node'interface'methods :: (RWCtx m s, ToPtr s (List (Mut s) (Method (Mut s)))) => Node'interface (Mut s) -> List (Mut s) (Method (Mut s)) -> m () Source #
has_Node'interface'methods :: ReadCtx m msg => Node'interface msg -> m Bool Source #
new_Node'interface'methods :: RWCtx m s => Int -> Node'interface (Mut s) -> m (List (Mut s) (Method (Mut s))) Source #
get_Node'interface'superclasses :: (ReadCtx m msg, FromPtr msg (List msg (Superclass msg))) => Node'interface msg -> m (List msg (Superclass msg)) Source #
set_Node'interface'superclasses :: (RWCtx m s, ToPtr s (List (Mut s) (Superclass (Mut s)))) => Node'interface (Mut s) -> List (Mut s) (Superclass (Mut s)) -> m () Source #
has_Node'interface'superclasses :: ReadCtx m msg => Node'interface msg -> m Bool Source #
new_Node'interface'superclasses :: RWCtx m s => Int -> Node'interface (Mut s) -> m (List (Mut s) (Superclass (Mut s))) Source #
newtype Node'const msg Source #
Node'const'newtype_ (Struct msg) |
Instances
ToStruct msg (Node'const msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Node'const msg -> Struct msg Source # | |
FromStruct msg (Node'const msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Node'const msg) Source # | |
MessageDefault (Node'const mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Node'const mut) Source # | |
HasMessage (Node'const mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Node'const mut -> Message mut Source # |
get_Node'const'type_ :: (ReadCtx m msg, FromPtr msg (Type msg)) => Node'const msg -> m (Type msg) Source #
set_Node'const'type_ :: (RWCtx m s, ToPtr s (Type (Mut s))) => Node'const (Mut s) -> Type (Mut s) -> m () Source #
has_Node'const'type_ :: ReadCtx m msg => Node'const msg -> m Bool Source #
new_Node'const'type_ :: RWCtx m s => Node'const (Mut s) -> m (Type (Mut s)) Source #
get_Node'const'value :: (ReadCtx m msg, FromPtr msg (Value msg)) => Node'const msg -> m (Value msg) Source #
set_Node'const'value :: (RWCtx m s, ToPtr s (Value (Mut s))) => Node'const (Mut s) -> Value (Mut s) -> m () Source #
has_Node'const'value :: ReadCtx m msg => Node'const msg -> m Bool Source #
new_Node'const'value :: RWCtx m s => Node'const (Mut s) -> m (Value (Mut s)) Source #
newtype Node'annotation msg Source #
Instances
ToStruct msg (Node'annotation msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Node'annotation msg -> Struct msg Source # | |
FromStruct msg (Node'annotation msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Node'annotation msg) Source # | |
MessageDefault (Node'annotation mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Node'annotation mut) Source # | |
HasMessage (Node'annotation mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Node'annotation mut -> Message mut Source # |
get_Node'annotation'type_ :: (ReadCtx m msg, FromPtr msg (Type msg)) => Node'annotation msg -> m (Type msg) Source #
set_Node'annotation'type_ :: (RWCtx m s, ToPtr s (Type (Mut s))) => Node'annotation (Mut s) -> Type (Mut s) -> m () Source #
has_Node'annotation'type_ :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
new_Node'annotation'type_ :: RWCtx m s => Node'annotation (Mut s) -> m (Type (Mut s)) Source #
get_Node'annotation'targetsFile :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsFile :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsConst :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsConst :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsEnum :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsEnum :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsEnumerant :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsEnumerant :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsStruct :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsStruct :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsField :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsField :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsUnion :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsUnion :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsGroup :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsGroup :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsInterface :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsInterface :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsMethod :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsMethod :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsParam :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsParam :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
get_Node'annotation'targetsAnnotation :: ReadCtx m msg => Node'annotation msg -> m Bool Source #
set_Node'annotation'targetsAnnotation :: RWCtx m s => Node'annotation (Mut s) -> Bool -> m () Source #
newtype Node'Parameter msg Source #
Instances
get_Node'Parameter'name :: (ReadCtx m msg, FromPtr msg (Text msg)) => Node'Parameter msg -> m (Text msg) Source #
set_Node'Parameter'name :: (RWCtx m s, ToPtr s (Text (Mut s))) => Node'Parameter (Mut s) -> Text (Mut s) -> m () Source #
has_Node'Parameter'name :: ReadCtx m msg => Node'Parameter msg -> m Bool Source #
new_Node'Parameter'name :: RWCtx m s => Int -> Node'Parameter (Mut s) -> m (Text (Mut s)) Source #
newtype Node'NestedNode msg Source #
Instances
get_Node'NestedNode'name :: (ReadCtx m msg, FromPtr msg (Text msg)) => Node'NestedNode msg -> m (Text msg) Source #
set_Node'NestedNode'name :: (RWCtx m s, ToPtr s (Text (Mut s))) => Node'NestedNode (Mut s) -> Text (Mut s) -> m () Source #
has_Node'NestedNode'name :: ReadCtx m msg => Node'NestedNode msg -> m Bool Source #
new_Node'NestedNode'name :: RWCtx m s => Int -> Node'NestedNode (Mut s) -> m (Text (Mut s)) Source #
get_Node'NestedNode'id :: ReadCtx m msg => Node'NestedNode msg -> m Word64 Source #
set_Node'NestedNode'id :: RWCtx m s => Node'NestedNode (Mut s) -> Word64 -> m () Source #
newtype Node'SourceInfo msg Source #
Instances
get_Node'SourceInfo'id :: ReadCtx m msg => Node'SourceInfo msg -> m Word64 Source #
set_Node'SourceInfo'id :: RWCtx m s => Node'SourceInfo (Mut s) -> Word64 -> m () Source #
get_Node'SourceInfo'docComment :: (ReadCtx m msg, FromPtr msg (Text msg)) => Node'SourceInfo msg -> m (Text msg) Source #
set_Node'SourceInfo'docComment :: (RWCtx m s, ToPtr s (Text (Mut s))) => Node'SourceInfo (Mut s) -> Text (Mut s) -> m () Source #
has_Node'SourceInfo'docComment :: ReadCtx m msg => Node'SourceInfo msg -> m Bool Source #
new_Node'SourceInfo'docComment :: RWCtx m s => Int -> Node'SourceInfo (Mut s) -> m (Text (Mut s)) Source #
get_Node'SourceInfo'members :: (ReadCtx m msg, FromPtr msg (List msg (Node'SourceInfo'Member msg))) => Node'SourceInfo msg -> m (List msg (Node'SourceInfo'Member msg)) Source #
set_Node'SourceInfo'members :: (RWCtx m s, ToPtr s (List (Mut s) (Node'SourceInfo'Member (Mut s)))) => Node'SourceInfo (Mut s) -> List (Mut s) (Node'SourceInfo'Member (Mut s)) -> m () Source #
has_Node'SourceInfo'members :: ReadCtx m msg => Node'SourceInfo msg -> m Bool Source #
new_Node'SourceInfo'members :: RWCtx m s => Int -> Node'SourceInfo (Mut s) -> m (List (Mut s) (Node'SourceInfo'Member (Mut s))) Source #
newtype Node'SourceInfo'Member msg Source #
Instances
get_Node'SourceInfo'Member'docComment :: (ReadCtx m msg, FromPtr msg (Text msg)) => Node'SourceInfo'Member msg -> m (Text msg) Source #
set_Node'SourceInfo'Member'docComment :: (RWCtx m s, ToPtr s (Text (Mut s))) => Node'SourceInfo'Member (Mut s) -> Text (Mut s) -> m () Source #
has_Node'SourceInfo'Member'docComment :: ReadCtx m msg => Node'SourceInfo'Member msg -> m Bool Source #
new_Node'SourceInfo'Member'docComment :: RWCtx m s => Int -> Node'SourceInfo'Member (Mut s) -> m (Text (Mut s)) Source #
Field'newtype_ (Struct msg) |
Instances
ToStruct msg (Field msg) Source # | |
FromStruct msg (Field msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
ToPtr s (Field ('Mut s)) Source # | |
FromPtr msg (Field msg) Source # | |
Allocate s (Field ('Mut s)) Source # | |
MutListElem s (Field ('Mut s)) Source # | |
ListElem mut (Field mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
MessageDefault (Field mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Field mut) mut Source # | |
newtype List mut (Field mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
set_Field'name :: (RWCtx m s, ToPtr s (Text (Mut s))) => Field (Mut s) -> Text (Mut s) -> m () Source #
get_Field'annotations :: (ReadCtx m msg, FromPtr msg (List msg (Annotation msg))) => Field msg -> m (List msg (Annotation msg)) Source #
set_Field'annotations :: (RWCtx m s, ToPtr s (List (Mut s) (Annotation (Mut s)))) => Field (Mut s) -> List (Mut s) (Annotation (Mut s)) -> m () Source #
new_Field'annotations :: RWCtx m s => Int -> Field (Mut s) -> m (List (Mut s) (Annotation (Mut s))) Source #
get_Field'ordinal :: (ReadCtx m msg, FromStruct msg (Field'ordinal msg)) => Field msg -> m (Field'ordinal msg) Source #
data Field' (mut :: Mutability) Source #
Field'slot (Field'slot mut) | |
Field'group (Field'group mut) | |
Field'unknown' Word16 |
Instances
FromStruct mut (Field' mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
get_Field' :: (ReadCtx m msg, FromStruct msg (Field' msg)) => Field msg -> m (Field' msg) Source #
set_Field'slot :: (RWCtx m s, FromStruct (Mut s) (Field'slot (Mut s))) => Field (Mut s) -> m (Field'slot (Mut s)) Source #
set_Field'group :: (RWCtx m s, FromStruct (Mut s) (Field'group (Mut s))) => Field (Mut s) -> m (Field'group (Mut s)) Source #
newtype Field'slot msg Source #
Field'slot'newtype_ (Struct msg) |
Instances
ToStruct msg (Field'slot msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Field'slot msg -> Struct msg Source # | |
FromStruct msg (Field'slot msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Field'slot msg) Source # | |
MessageDefault (Field'slot mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Field'slot mut) Source # | |
HasMessage (Field'slot mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Field'slot mut -> Message mut Source # |
get_Field'slot'offset :: ReadCtx m msg => Field'slot msg -> m Word32 Source #
set_Field'slot'offset :: RWCtx m s => Field'slot (Mut s) -> Word32 -> m () Source #
get_Field'slot'type_ :: (ReadCtx m msg, FromPtr msg (Type msg)) => Field'slot msg -> m (Type msg) Source #
set_Field'slot'type_ :: (RWCtx m s, ToPtr s (Type (Mut s))) => Field'slot (Mut s) -> Type (Mut s) -> m () Source #
has_Field'slot'type_ :: ReadCtx m msg => Field'slot msg -> m Bool Source #
new_Field'slot'type_ :: RWCtx m s => Field'slot (Mut s) -> m (Type (Mut s)) Source #
get_Field'slot'defaultValue :: (ReadCtx m msg, FromPtr msg (Value msg)) => Field'slot msg -> m (Value msg) Source #
set_Field'slot'defaultValue :: (RWCtx m s, ToPtr s (Value (Mut s))) => Field'slot (Mut s) -> Value (Mut s) -> m () Source #
has_Field'slot'defaultValue :: ReadCtx m msg => Field'slot msg -> m Bool Source #
new_Field'slot'defaultValue :: RWCtx m s => Field'slot (Mut s) -> m (Value (Mut s)) Source #
get_Field'slot'hadExplicitDefault :: ReadCtx m msg => Field'slot msg -> m Bool Source #
set_Field'slot'hadExplicitDefault :: RWCtx m s => Field'slot (Mut s) -> Bool -> m () Source #
newtype Field'group msg Source #
Field'group'newtype_ (Struct msg) |
Instances
ToStruct msg (Field'group msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Field'group msg -> Struct msg Source # | |
FromStruct msg (Field'group msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Field'group msg) Source # | |
MessageDefault (Field'group mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Field'group mut) Source # | |
HasMessage (Field'group mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Field'group mut -> Message mut Source # |
get_Field'group'typeId :: ReadCtx m msg => Field'group msg -> m Word64 Source #
set_Field'group'typeId :: RWCtx m s => Field'group (Mut s) -> Word64 -> m () Source #
newtype Field'ordinal msg Source #
Field'ordinal'newtype_ (Struct msg) |
Instances
ToStruct msg (Field'ordinal msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Field'ordinal msg -> Struct msg Source # | |
FromStruct msg (Field'ordinal msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Field'ordinal msg) Source # | |
MessageDefault (Field'ordinal mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Field'ordinal mut) Source # | |
HasMessage (Field'ordinal mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Field'ordinal mut -> Message mut Source # |
data Field'ordinal' (mut :: Mutability) Source #
Instances
FromStruct mut (Field'ordinal' mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m mut => Struct mut -> m (Field'ordinal' mut) Source # |
get_Field'ordinal' :: (ReadCtx m msg, FromStruct msg (Field'ordinal' msg)) => Field'ordinal msg -> m (Field'ordinal' msg) Source #
set_Field'ordinal'implicit :: RWCtx m s => Field'ordinal (Mut s) -> m () Source #
set_Field'ordinal'explicit :: RWCtx m s => Field'ordinal (Mut s) -> Word16 -> m () Source #
set_Field'ordinal'unknown' :: RWCtx m s => Field'ordinal (Mut s) -> Word16 -> m () Source #
newtype Enumerant msg Source #
Enumerant'newtype_ (Struct msg) |
Instances
ToStruct msg (Enumerant msg) Source # | |
FromStruct msg (Enumerant msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
ToPtr s (Enumerant ('Mut s)) Source # | |
FromPtr msg (Enumerant msg) Source # | |
Allocate s (Enumerant ('Mut s)) Source # | |
MutListElem s (Enumerant ('Mut s)) Source # | |
ListElem mut (Enumerant mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Enumerant mut)) Source # toUntypedList :: List mut (Enumerant mut) -> List mut Source # length :: List mut (Enumerant mut) -> Int Source # index :: ReadCtx m mut => Int -> List mut (Enumerant mut) -> m (Enumerant mut) Source # | |
MessageDefault (Enumerant mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Enumerant mut) mut Source # | |
newtype List mut (Enumerant mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
get_Enumerant'name :: (ReadCtx m msg, FromPtr msg (Text msg)) => Enumerant msg -> m (Text msg) Source #
set_Enumerant'name :: (RWCtx m s, ToPtr s (Text (Mut s))) => Enumerant (Mut s) -> Text (Mut s) -> m () Source #
get_Enumerant'annotations :: (ReadCtx m msg, FromPtr msg (List msg (Annotation msg))) => Enumerant msg -> m (List msg (Annotation msg)) Source #
set_Enumerant'annotations :: (RWCtx m s, ToPtr s (List (Mut s) (Annotation (Mut s)))) => Enumerant (Mut s) -> List (Mut s) (Annotation (Mut s)) -> m () Source #
new_Enumerant'annotations :: RWCtx m s => Int -> Enumerant (Mut s) -> m (List (Mut s) (Annotation (Mut s))) Source #
newtype Superclass msg Source #
Superclass'newtype_ (Struct msg) |
Instances
get_Superclass'id :: ReadCtx m msg => Superclass msg -> m Word64 Source #
set_Superclass'id :: RWCtx m s => Superclass (Mut s) -> Word64 -> m () Source #
get_Superclass'brand :: (ReadCtx m msg, FromPtr msg (Brand msg)) => Superclass msg -> m (Brand msg) Source #
set_Superclass'brand :: (RWCtx m s, ToPtr s (Brand (Mut s))) => Superclass (Mut s) -> Brand (Mut s) -> m () Source #
has_Superclass'brand :: ReadCtx m msg => Superclass msg -> m Bool Source #
new_Superclass'brand :: RWCtx m s => Superclass (Mut s) -> m (Brand (Mut s)) Source #
Method'newtype_ (Struct msg) |
Instances
ToStruct msg (Method msg) Source # | |
FromStruct msg (Method msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
ToPtr s (Method ('Mut s)) Source # | |
FromPtr msg (Method msg) Source # | |
Allocate s (Method ('Mut s)) Source # | |
MutListElem s (Method ('Mut s)) Source # | |
ListElem mut (Method mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
MessageDefault (Method mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Method mut) mut Source # | |
newtype List mut (Method mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
set_Method'name :: (RWCtx m s, ToPtr s (Text (Mut s))) => Method (Mut s) -> Text (Mut s) -> m () Source #
get_Method'annotations :: (ReadCtx m msg, FromPtr msg (List msg (Annotation msg))) => Method msg -> m (List msg (Annotation msg)) Source #
set_Method'annotations :: (RWCtx m s, ToPtr s (List (Mut s) (Annotation (Mut s)))) => Method (Mut s) -> List (Mut s) (Annotation (Mut s)) -> m () Source #
new_Method'annotations :: RWCtx m s => Int -> Method (Mut s) -> m (List (Mut s) (Annotation (Mut s))) Source #
get_Method'paramBrand :: (ReadCtx m msg, FromPtr msg (Brand msg)) => Method msg -> m (Brand msg) Source #
set_Method'paramBrand :: (RWCtx m s, ToPtr s (Brand (Mut s))) => Method (Mut s) -> Brand (Mut s) -> m () Source #
get_Method'resultBrand :: (ReadCtx m msg, FromPtr msg (Brand msg)) => Method msg -> m (Brand msg) Source #
set_Method'resultBrand :: (RWCtx m s, ToPtr s (Brand (Mut s))) => Method (Mut s) -> Brand (Mut s) -> m () Source #
get_Method'implicitParameters :: (ReadCtx m msg, FromPtr msg (List msg (Node'Parameter msg))) => Method msg -> m (List msg (Node'Parameter msg)) Source #
set_Method'implicitParameters :: (RWCtx m s, ToPtr s (List (Mut s) (Node'Parameter (Mut s)))) => Method (Mut s) -> List (Mut s) (Node'Parameter (Mut s)) -> m () Source #
new_Method'implicitParameters :: RWCtx m s => Int -> Method (Mut s) -> m (List (Mut s) (Node'Parameter (Mut s))) Source #
Type'newtype_ (Struct msg) |
Instances
ToStruct msg (Type msg) Source # | |
FromStruct msg (Type msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
ToPtr s (Type ('Mut s)) Source # | |
FromPtr msg (Type msg) Source # | |
Allocate s (Type ('Mut s)) Source # | |
MutListElem s (Type ('Mut s)) Source # | |
ListElem mut (Type mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
MessageDefault (Type mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Type mut) mut Source # | |
newtype List mut (Type mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
data Type' (mut :: Mutability) Source #
Instances
FromStruct mut (Type' mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
set_Type'list :: (RWCtx m s, FromStruct (Mut s) (Type'list (Mut s))) => Type (Mut s) -> m (Type'list (Mut s)) Source #
set_Type'enum :: (RWCtx m s, FromStruct (Mut s) (Type'enum (Mut s))) => Type (Mut s) -> m (Type'enum (Mut s)) Source #
set_Type'struct :: (RWCtx m s, FromStruct (Mut s) (Type'struct (Mut s))) => Type (Mut s) -> m (Type'struct (Mut s)) Source #
set_Type'interface :: (RWCtx m s, FromStruct (Mut s) (Type'interface (Mut s))) => Type (Mut s) -> m (Type'interface (Mut s)) Source #
set_Type'anyPointer :: (RWCtx m s, FromStruct (Mut s) (Type'anyPointer (Mut s))) => Type (Mut s) -> m (Type'anyPointer (Mut s)) Source #
newtype Type'list msg Source #
Type'list'newtype_ (Struct msg) |
Instances
ToStruct msg (Type'list msg) Source # | |
FromStruct msg (Type'list msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
MessageDefault (Type'list mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Type'list mut) mut Source # | |
get_Type'list'elementType :: (ReadCtx m msg, FromPtr msg (Type msg)) => Type'list msg -> m (Type msg) Source #
set_Type'list'elementType :: (RWCtx m s, ToPtr s (Type (Mut s))) => Type'list (Mut s) -> Type (Mut s) -> m () Source #
newtype Type'enum msg Source #
Type'enum'newtype_ (Struct msg) |
Instances
ToStruct msg (Type'enum msg) Source # | |
FromStruct msg (Type'enum msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
MessageDefault (Type'enum mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Type'enum mut) mut Source # | |
get_Type'enum'brand :: (ReadCtx m msg, FromPtr msg (Brand msg)) => Type'enum msg -> m (Brand msg) Source #
set_Type'enum'brand :: (RWCtx m s, ToPtr s (Brand (Mut s))) => Type'enum (Mut s) -> Brand (Mut s) -> m () Source #
newtype Type'struct msg Source #
Type'struct'newtype_ (Struct msg) |
Instances
ToStruct msg (Type'struct msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Type'struct msg -> Struct msg Source # | |
FromStruct msg (Type'struct msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Type'struct msg) Source # | |
MessageDefault (Type'struct mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Type'struct mut) Source # | |
HasMessage (Type'struct mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Type'struct mut -> Message mut Source # |
get_Type'struct'typeId :: ReadCtx m msg => Type'struct msg -> m Word64 Source #
set_Type'struct'typeId :: RWCtx m s => Type'struct (Mut s) -> Word64 -> m () Source #
get_Type'struct'brand :: (ReadCtx m msg, FromPtr msg (Brand msg)) => Type'struct msg -> m (Brand msg) Source #
set_Type'struct'brand :: (RWCtx m s, ToPtr s (Brand (Mut s))) => Type'struct (Mut s) -> Brand (Mut s) -> m () Source #
has_Type'struct'brand :: ReadCtx m msg => Type'struct msg -> m Bool Source #
new_Type'struct'brand :: RWCtx m s => Type'struct (Mut s) -> m (Brand (Mut s)) Source #
newtype Type'interface msg Source #
Instances
ToStruct msg (Type'interface msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Type'interface msg -> Struct msg Source # | |
FromStruct msg (Type'interface msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Type'interface msg) Source # | |
MessageDefault (Type'interface mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Type'interface mut) Source # | |
HasMessage (Type'interface mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Type'interface mut -> Message mut Source # |
get_Type'interface'typeId :: ReadCtx m msg => Type'interface msg -> m Word64 Source #
set_Type'interface'typeId :: RWCtx m s => Type'interface (Mut s) -> Word64 -> m () Source #
get_Type'interface'brand :: (ReadCtx m msg, FromPtr msg (Brand msg)) => Type'interface msg -> m (Brand msg) Source #
set_Type'interface'brand :: (RWCtx m s, ToPtr s (Brand (Mut s))) => Type'interface (Mut s) -> Brand (Mut s) -> m () Source #
has_Type'interface'brand :: ReadCtx m msg => Type'interface msg -> m Bool Source #
new_Type'interface'brand :: RWCtx m s => Type'interface (Mut s) -> m (Brand (Mut s)) Source #
newtype Type'anyPointer msg Source #
Instances
ToStruct msg (Type'anyPointer msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Type'anyPointer msg -> Struct msg Source # | |
FromStruct msg (Type'anyPointer msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Type'anyPointer msg) Source # | |
MessageDefault (Type'anyPointer mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Type'anyPointer mut) Source # | |
HasMessage (Type'anyPointer mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Type'anyPointer mut -> Message mut Source # |
data Type'anyPointer' (mut :: Mutability) Source #
Instances
FromStruct mut (Type'anyPointer' mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m mut => Struct mut -> m (Type'anyPointer' mut) Source # |
get_Type'anyPointer' :: (ReadCtx m msg, FromStruct msg (Type'anyPointer' msg)) => Type'anyPointer msg -> m (Type'anyPointer' msg) Source #
set_Type'anyPointer'unconstrained :: (RWCtx m s, FromStruct (Mut s) (Type'anyPointer'unconstrained (Mut s))) => Type'anyPointer (Mut s) -> m (Type'anyPointer'unconstrained (Mut s)) Source #
set_Type'anyPointer'parameter :: (RWCtx m s, FromStruct (Mut s) (Type'anyPointer'parameter (Mut s))) => Type'anyPointer (Mut s) -> m (Type'anyPointer'parameter (Mut s)) Source #
set_Type'anyPointer'implicitMethodParameter :: (RWCtx m s, FromStruct (Mut s) (Type'anyPointer'implicitMethodParameter (Mut s))) => Type'anyPointer (Mut s) -> m (Type'anyPointer'implicitMethodParameter (Mut s)) Source #
set_Type'anyPointer'unknown' :: RWCtx m s => Type'anyPointer (Mut s) -> Word16 -> m () Source #
newtype Type'anyPointer'unconstrained msg Source #
Instances
ToStruct msg (Type'anyPointer'unconstrained msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Type'anyPointer'unconstrained msg -> Struct msg Source # | |
FromStruct msg (Type'anyPointer'unconstrained msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Type'anyPointer'unconstrained msg) Source # | |
MessageDefault (Type'anyPointer'unconstrained mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Type'anyPointer'unconstrained mut) Source # | |
HasMessage (Type'anyPointer'unconstrained mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Type'anyPointer'unconstrained mut -> Message mut Source # |
data Type'anyPointer'unconstrained' (mut :: Mutability) Source #
Type'anyPointer'unconstrained'anyKind | |
Type'anyPointer'unconstrained'struct | |
Type'anyPointer'unconstrained'list | |
Type'anyPointer'unconstrained'capability | |
Type'anyPointer'unconstrained'unknown' Word16 |
Instances
FromStruct mut (Type'anyPointer'unconstrained' mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m mut => Struct mut -> m (Type'anyPointer'unconstrained' mut) Source # |
get_Type'anyPointer'unconstrained' :: (ReadCtx m msg, FromStruct msg (Type'anyPointer'unconstrained' msg)) => Type'anyPointer'unconstrained msg -> m (Type'anyPointer'unconstrained' msg) Source #
set_Type'anyPointer'unconstrained'anyKind :: RWCtx m s => Type'anyPointer'unconstrained (Mut s) -> m () Source #
set_Type'anyPointer'unconstrained'struct :: RWCtx m s => Type'anyPointer'unconstrained (Mut s) -> m () Source #
set_Type'anyPointer'unconstrained'list :: RWCtx m s => Type'anyPointer'unconstrained (Mut s) -> m () Source #
set_Type'anyPointer'unconstrained'capability :: RWCtx m s => Type'anyPointer'unconstrained (Mut s) -> m () Source #
set_Type'anyPointer'unconstrained'unknown' :: RWCtx m s => Type'anyPointer'unconstrained (Mut s) -> Word16 -> m () Source #
newtype Type'anyPointer'parameter msg Source #
Instances
ToStruct msg (Type'anyPointer'parameter msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Type'anyPointer'parameter msg -> Struct msg Source # | |
FromStruct msg (Type'anyPointer'parameter msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Type'anyPointer'parameter msg) Source # | |
MessageDefault (Type'anyPointer'parameter mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Type'anyPointer'parameter mut) Source # | |
HasMessage (Type'anyPointer'parameter mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Type'anyPointer'parameter mut -> Message mut Source # |
get_Type'anyPointer'parameter'scopeId :: ReadCtx m msg => Type'anyPointer'parameter msg -> m Word64 Source #
set_Type'anyPointer'parameter'scopeId :: RWCtx m s => Type'anyPointer'parameter (Mut s) -> Word64 -> m () Source #
get_Type'anyPointer'parameter'parameterIndex :: ReadCtx m msg => Type'anyPointer'parameter msg -> m Word16 Source #
set_Type'anyPointer'parameter'parameterIndex :: RWCtx m s => Type'anyPointer'parameter (Mut s) -> Word16 -> m () Source #
newtype Type'anyPointer'implicitMethodParameter msg Source #
Instances
ToStruct msg (Type'anyPointer'implicitMethodParameter msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema toStruct :: Type'anyPointer'implicitMethodParameter msg -> Struct msg Source # | |
FromStruct msg (Type'anyPointer'implicitMethodParameter msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m msg => Struct msg -> m (Type'anyPointer'implicitMethodParameter msg) Source # | |
MessageDefault (Type'anyPointer'implicitMethodParameter mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema messageDefault :: ReadCtx m mut => Message mut -> m (Type'anyPointer'implicitMethodParameter mut) Source # | |
HasMessage (Type'anyPointer'implicitMethodParameter mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema message :: Type'anyPointer'implicitMethodParameter mut -> Message mut Source # |
get_Type'anyPointer'implicitMethodParameter'parameterIndex :: ReadCtx m msg => Type'anyPointer'implicitMethodParameter msg -> m Word16 Source #
set_Type'anyPointer'implicitMethodParameter'parameterIndex :: RWCtx m s => Type'anyPointer'implicitMethodParameter (Mut s) -> Word16 -> m () Source #
Brand'newtype_ (Struct msg) |
Instances
ToStruct msg (Brand msg) Source # | |
FromStruct msg (Brand msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
ToPtr s (Brand ('Mut s)) Source # | |
FromPtr msg (Brand msg) Source # | |
Allocate s (Brand ('Mut s)) Source # | |
MutListElem s (Brand ('Mut s)) Source # | |
ListElem mut (Brand mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
MessageDefault (Brand mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Brand mut) mut Source # | |
newtype List mut (Brand mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
get_Brand'scopes :: (ReadCtx m msg, FromPtr msg (List msg (Brand'Scope msg))) => Brand msg -> m (List msg (Brand'Scope msg)) Source #
set_Brand'scopes :: (RWCtx m s, ToPtr s (List (Mut s) (Brand'Scope (Mut s)))) => Brand (Mut s) -> List (Mut s) (Brand'Scope (Mut s)) -> m () Source #
new_Brand'scopes :: RWCtx m s => Int -> Brand (Mut s) -> m (List (Mut s) (Brand'Scope (Mut s))) Source #
newtype Brand'Scope msg Source #
Brand'Scope'newtype_ (Struct msg) |
Instances
get_Brand'Scope'scopeId :: ReadCtx m msg => Brand'Scope msg -> m Word64 Source #
set_Brand'Scope'scopeId :: RWCtx m s => Brand'Scope (Mut s) -> Word64 -> m () Source #
data Brand'Scope' (mut :: Mutability) Source #
Instances
FromStruct mut (Brand'Scope' mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m mut => Struct mut -> m (Brand'Scope' mut) Source # |
get_Brand'Scope' :: (ReadCtx m msg, FromStruct msg (Brand'Scope' msg)) => Brand'Scope msg -> m (Brand'Scope' msg) Source #
set_Brand'Scope'bind :: (RWCtx m s, ToPtr s (List (Mut s) (Brand'Binding (Mut s)))) => Brand'Scope (Mut s) -> List (Mut s) (Brand'Binding (Mut s)) -> m () Source #
set_Brand'Scope'inherit :: RWCtx m s => Brand'Scope (Mut s) -> m () Source #
set_Brand'Scope'unknown' :: RWCtx m s => Brand'Scope (Mut s) -> Word16 -> m () Source #
newtype Brand'Binding msg Source #
Brand'Binding'newtype_ (Struct msg) |
Instances
data Brand'Binding' (mut :: Mutability) Source #
Instances
FromStruct mut (Brand'Binding' mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema fromStruct :: ReadCtx m mut => Struct mut -> m (Brand'Binding' mut) Source # |
get_Brand'Binding' :: (ReadCtx m msg, FromStruct msg (Brand'Binding' msg)) => Brand'Binding msg -> m (Brand'Binding' msg) Source #
set_Brand'Binding'unbound :: RWCtx m s => Brand'Binding (Mut s) -> m () Source #
set_Brand'Binding'type_ :: (RWCtx m s, ToPtr s (Type (Mut s))) => Brand'Binding (Mut s) -> Type (Mut s) -> m () Source #
set_Brand'Binding'unknown' :: RWCtx m s => Brand'Binding (Mut s) -> Word16 -> m () Source #
Value'newtype_ (Struct msg) |
Instances
ToStruct msg (Value msg) Source # | |
FromStruct msg (Value msg) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
ToPtr s (Value ('Mut s)) Source # | |
FromPtr msg (Value msg) Source # | |
Allocate s (Value ('Mut s)) Source # | |
MutListElem s (Value ('Mut s)) Source # | |
ListElem mut (Value mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
MessageDefault (Value mut) mut Source # | |
Defined in Capnp.Gen.Capnp.Schema | |
HasMessage (Value mut) mut Source # | |
newtype List mut (Value mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
data Value' (mut :: Mutability) Source #
Instances
FromStruct mut (Value' mut) Source # | |
Defined in Capnp.Gen.Capnp.Schema |
get_Value' :: (ReadCtx m msg, FromStruct msg (Value' msg)) => Value msg -> m (Value' msg) Source #
set_Value'text :: (RWCtx m s, ToPtr s (Text (Mut s))) => Value (Mut s) -> Text (Mut s) -> m () Source #
set_Value'data_ :: (RWCtx m s, ToPtr s (Data (Mut s))) => Value (Mut s) -> Data (Mut s) -> m () Source #
set_Value'list :: (RWCtx m s, ToPtr s (Maybe (Ptr (Mut s)))) => Value (Mut s) -> Maybe (Ptr (Mut s)) -> m () Source #
set_Value'struct :: (RWCtx m s, ToPtr s (Maybe (Ptr (Mut s)))) => Value (Mut s) -> Maybe (Ptr (Mut s)) -> m () Source #
set_Value'anyPointer :: (RWCtx m s, ToPtr s (Maybe (Ptr (Mut s)))) => Value (Mut s) -> Maybe (Ptr (Mut s)) -> m () Source #
newtype Annotation msg Source #
Annotation'newtype_ (Struct msg) |
Instances
get_Annotation'id :: ReadCtx m msg => Annotation msg -> m Word64 Source #
set_Annotation'id :: RWCtx m s => Annotation (Mut s) -> Word64 -> m () Source #
get_Annotation'value :: (ReadCtx m msg, FromPtr msg (Value msg)) => Annotation msg -> m (Value msg) Source #
set_Annotation'value :: (RWCtx m s, ToPtr s (Value (Mut s))) => Annotation (Mut s) -> Value (Mut s) -> m () Source #
has_Annotation'value :: ReadCtx m msg => Annotation msg -> m Bool Source #
new_Annotation'value :: RWCtx m s => Annotation (Mut s) -> m (Value (Mut s)) Source #
get_Annotation'brand :: (ReadCtx m msg, FromPtr msg (Brand msg)) => Annotation msg -> m (Brand msg) Source #
set_Annotation'brand :: (RWCtx m s, ToPtr s (Brand (Mut s))) => Annotation (Mut s) -> Brand (Mut s) -> m () Source #
has_Annotation'brand :: ReadCtx m msg => Annotation msg -> m Bool Source #
new_Annotation'brand :: RWCtx m s => Annotation (Mut s) -> m (Brand (Mut s)) Source #
data ElementSize Source #
ElementSize'empty | |
ElementSize'bit | |
ElementSize'byte | |
ElementSize'twoBytes | |
ElementSize'fourBytes | |
ElementSize'eightBytes | |
ElementSize'pointer | |
ElementSize'inlineComposite | |
ElementSize'unknown' Word16 |
Instances
newtype CapnpVersion msg Source #
CapnpVersion'newtype_ (Struct msg) |
Instances
get_CapnpVersion'major :: ReadCtx m msg => CapnpVersion msg -> m Word16 Source #
set_CapnpVersion'major :: RWCtx m s => CapnpVersion (Mut s) -> Word16 -> m () Source #
get_CapnpVersion'minor :: ReadCtx m msg => CapnpVersion msg -> m Word8 Source #
set_CapnpVersion'minor :: RWCtx m s => CapnpVersion (Mut s) -> Word8 -> m () Source #
get_CapnpVersion'micro :: ReadCtx m msg => CapnpVersion msg -> m Word8 Source #
set_CapnpVersion'micro :: RWCtx m s => CapnpVersion (Mut s) -> Word8 -> m () Source #
newtype CodeGeneratorRequest msg Source #
Instances
get_CodeGeneratorRequest'nodes :: (ReadCtx m msg, FromPtr msg (List msg (Node msg))) => CodeGeneratorRequest msg -> m (List msg (Node msg)) Source #
set_CodeGeneratorRequest'nodes :: (RWCtx m s, ToPtr s (List (Mut s) (Node (Mut s)))) => CodeGeneratorRequest (Mut s) -> List (Mut s) (Node (Mut s)) -> m () Source #
has_CodeGeneratorRequest'nodes :: ReadCtx m msg => CodeGeneratorRequest msg -> m Bool Source #
new_CodeGeneratorRequest'nodes :: RWCtx m s => Int -> CodeGeneratorRequest (Mut s) -> m (List (Mut s) (Node (Mut s))) Source #
get_CodeGeneratorRequest'requestedFiles :: (ReadCtx m msg, FromPtr msg (List msg (CodeGeneratorRequest'RequestedFile msg))) => CodeGeneratorRequest msg -> m (List msg (CodeGeneratorRequest'RequestedFile msg)) Source #
set_CodeGeneratorRequest'requestedFiles :: (RWCtx m s, ToPtr s (List (Mut s) (CodeGeneratorRequest'RequestedFile (Mut s)))) => CodeGeneratorRequest (Mut s) -> List (Mut s) (CodeGeneratorRequest'RequestedFile (Mut s)) -> m () Source #
has_CodeGeneratorRequest'requestedFiles :: ReadCtx m msg => CodeGeneratorRequest msg -> m Bool Source #
new_CodeGeneratorRequest'requestedFiles :: RWCtx m s => Int -> CodeGeneratorRequest (Mut s) -> m (List (Mut s) (CodeGeneratorRequest'RequestedFile (Mut s))) Source #
get_CodeGeneratorRequest'capnpVersion :: (ReadCtx m msg, FromPtr msg (CapnpVersion msg)) => CodeGeneratorRequest msg -> m (CapnpVersion msg) Source #
set_CodeGeneratorRequest'capnpVersion :: (RWCtx m s, ToPtr s (CapnpVersion (Mut s))) => CodeGeneratorRequest (Mut s) -> CapnpVersion (Mut s) -> m () Source #
has_CodeGeneratorRequest'capnpVersion :: ReadCtx m msg => CodeGeneratorRequest msg -> m Bool Source #
new_CodeGeneratorRequest'capnpVersion :: RWCtx m s => CodeGeneratorRequest (Mut s) -> m (CapnpVersion (Mut s)) Source #
get_CodeGeneratorRequest'sourceInfo :: (ReadCtx m msg, FromPtr msg (List msg (Node'SourceInfo msg))) => CodeGeneratorRequest msg -> m (List msg (Node'SourceInfo msg)) Source #
set_CodeGeneratorRequest'sourceInfo :: (RWCtx m s, ToPtr s (List (Mut s) (Node'SourceInfo (Mut s)))) => CodeGeneratorRequest (Mut s) -> List (Mut s) (Node'SourceInfo (Mut s)) -> m () Source #
has_CodeGeneratorRequest'sourceInfo :: ReadCtx m msg => CodeGeneratorRequest msg -> m Bool Source #
new_CodeGeneratorRequest'sourceInfo :: RWCtx m s => Int -> CodeGeneratorRequest (Mut s) -> m (List (Mut s) (Node'SourceInfo (Mut s))) Source #
newtype CodeGeneratorRequest'RequestedFile msg Source #
Instances
get_CodeGeneratorRequest'RequestedFile'id :: ReadCtx m msg => CodeGeneratorRequest'RequestedFile msg -> m Word64 Source #
set_CodeGeneratorRequest'RequestedFile'id :: RWCtx m s => CodeGeneratorRequest'RequestedFile (Mut s) -> Word64 -> m () Source #
get_CodeGeneratorRequest'RequestedFile'filename :: (ReadCtx m msg, FromPtr msg (Text msg)) => CodeGeneratorRequest'RequestedFile msg -> m (Text msg) Source #
set_CodeGeneratorRequest'RequestedFile'filename :: (RWCtx m s, ToPtr s (Text (Mut s))) => CodeGeneratorRequest'RequestedFile (Mut s) -> Text (Mut s) -> m () Source #
has_CodeGeneratorRequest'RequestedFile'filename :: ReadCtx m msg => CodeGeneratorRequest'RequestedFile msg -> m Bool Source #
new_CodeGeneratorRequest'RequestedFile'filename :: RWCtx m s => Int -> CodeGeneratorRequest'RequestedFile (Mut s) -> m (Text (Mut s)) Source #
get_CodeGeneratorRequest'RequestedFile'imports :: (ReadCtx m msg, FromPtr msg (List msg (CodeGeneratorRequest'RequestedFile'Import msg))) => CodeGeneratorRequest'RequestedFile msg -> m (List msg (CodeGeneratorRequest'RequestedFile'Import msg)) Source #
set_CodeGeneratorRequest'RequestedFile'imports :: (RWCtx m s, ToPtr s (List (Mut s) (CodeGeneratorRequest'RequestedFile'Import (Mut s)))) => CodeGeneratorRequest'RequestedFile (Mut s) -> List (Mut s) (CodeGeneratorRequest'RequestedFile'Import (Mut s)) -> m () Source #
has_CodeGeneratorRequest'RequestedFile'imports :: ReadCtx m msg => CodeGeneratorRequest'RequestedFile msg -> m Bool Source #
new_CodeGeneratorRequest'RequestedFile'imports :: RWCtx m s => Int -> CodeGeneratorRequest'RequestedFile (Mut s) -> m (List (Mut s) (CodeGeneratorRequest'RequestedFile'Import (Mut s))) Source #
newtype CodeGeneratorRequest'RequestedFile'Import msg Source #
Instances
get_CodeGeneratorRequest'RequestedFile'Import'id :: ReadCtx m msg => CodeGeneratorRequest'RequestedFile'Import msg -> m Word64 Source #
set_CodeGeneratorRequest'RequestedFile'Import'id :: RWCtx m s => CodeGeneratorRequest'RequestedFile'Import (Mut s) -> Word64 -> m () Source #
get_CodeGeneratorRequest'RequestedFile'Import'name :: (ReadCtx m msg, FromPtr msg (Text msg)) => CodeGeneratorRequest'RequestedFile'Import msg -> m (Text msg) Source #
set_CodeGeneratorRequest'RequestedFile'Import'name :: (RWCtx m s, ToPtr s (Text (Mut s))) => CodeGeneratorRequest'RequestedFile'Import (Mut s) -> Text (Mut s) -> m () Source #
has_CodeGeneratorRequest'RequestedFile'Import'name :: ReadCtx m msg => CodeGeneratorRequest'RequestedFile'Import msg -> m Bool Source #
new_CodeGeneratorRequest'RequestedFile'Import'name :: RWCtx m s => Int -> CodeGeneratorRequest'RequestedFile'Import (Mut s) -> m (Text (Mut s)) Source #