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

Capnp.Gen.Capnp.Schema

Documentation

newtype Node msg Source #

Constructors

Node'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: Node msg -> Struct msg Source #

FromStruct msg (Node msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Node ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Node msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

ListElem mut (Node mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Node mut)) Source #

toUntypedList :: List mut (Node mut) -> List mut Source #

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

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

MessageDefault (Node mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (Node mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Node mut -> Message mut Source #

newtype List mut (Node mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Node mut) = Node'List_ (ListOf mut (Struct mut))

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

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

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 #

new_Node'displayName :: RWCtx m s => Int -> Node (Mut s) -> m (Text (Mut s)) Source #

set_Node'scopeId :: RWCtx m s => Node (Mut s) -> Word64 -> 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 #

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 #

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

data Node' (mut :: Mutability) Source #

Instances

Instances details
FromStruct mut (Node' mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

set_Node'file :: RWCtx m s => Node (Mut s) -> m () 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'const :: (RWCtx m s, FromStruct (Mut s) (Node'const (Mut s))) => Node (Mut s) -> m (Node'const (Mut s)) Source #

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

newtype Node'struct msg Source #

Constructors

Node'struct'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Node'struct mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Node'struct mut) Source #

HasMessage (Node'struct mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Node'struct mut -> Message mut 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 #

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 #

Constructors

Node'enum'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Node'enum mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Node'enum mut) Source #

HasMessage (Node'enum mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Node'enum mut -> Message 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 #

newtype Node'interface msg Source #

Constructors

Node'interface'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Node'interface mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Node'interface mut) Source #

HasMessage (Node'interface mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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 #

newtype Node'const msg Source #

Constructors

Node'const'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Node'const mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Node'const mut) Source #

HasMessage (Node'const mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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 #

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 #

newtype Node'annotation msg Source #

Constructors

Node'annotation'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Node'annotation mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Node'annotation mut) Source #

HasMessage (Node'annotation mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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 #

newtype Node'Parameter msg Source #

Constructors

Node'Parameter'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Node'Parameter ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node'Parameter mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Node'Parameter mut)) Source #

toUntypedList :: List mut (Node'Parameter mut) -> List mut Source #

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Node'Parameter mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Node'Parameter mut -> Message mut Source #

newtype List mut (Node'Parameter mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Node'Parameter mut) = Node'Parameter'List_ (ListOf mut (Struct mut))

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 #

newtype Node'NestedNode msg Source #

Constructors

Node'NestedNode'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Node'NestedNode ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node'NestedNode mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Node'NestedNode mut)) Source #

toUntypedList :: List mut (Node'NestedNode mut) -> List mut Source #

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Node'NestedNode mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Node'NestedNode mut -> Message mut Source #

newtype List mut (Node'NestedNode mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Node'NestedNode mut) = Node'NestedNode'List_ (ListOf mut (Struct mut))

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 #

newtype Node'SourceInfo msg Source #

Constructors

Node'SourceInfo'newtype_ (Struct msg) 

Instances

Instances details
ToStruct msg (Node'SourceInfo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Node'SourceInfo ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Node'SourceInfo msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (Node'SourceInfo ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Node'SourceInfo ('Mut s)) Source #

MutListElem s (Node'SourceInfo ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

ListElem mut (Node'SourceInfo mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node'SourceInfo mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Node'SourceInfo mut)) Source #

toUntypedList :: List mut (Node'SourceInfo mut) -> List mut Source #

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

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

MessageDefault (Node'SourceInfo mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Node'SourceInfo mut) Source #

HasMessage (Node'SourceInfo mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Node'SourceInfo mut -> Message mut Source #

newtype List mut (Node'SourceInfo mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Node'SourceInfo mut) = Node'SourceInfo'List_ (ListOf mut (Struct mut))

newtype Node'SourceInfo'Member msg Source #

Instances

Instances details
ToStruct msg (Node'SourceInfo'Member msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

FromStruct msg (Node'SourceInfo'Member msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Node'SourceInfo'Member ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

toPtr :: WriteCtx m s => Message ('Mut s) -> Node'SourceInfo'Member ('Mut s) -> m (Maybe (Ptr ('Mut s))) Source #

FromPtr msg (Node'SourceInfo'Member msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (Node'SourceInfo'Member ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Node'SourceInfo'Member ('Mut s)) Source #

MutListElem s (Node'SourceInfo'Member ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Node'SourceInfo'Member ('Mut s))) Source #

ListElem mut (Node'SourceInfo'Member mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Node'SourceInfo'Member mut) Source #

MessageDefault (Node'SourceInfo'Member mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Node'SourceInfo'Member mut) Source #

HasMessage (Node'SourceInfo'Member mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Node'SourceInfo'Member mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype Field msg Source #

Constructors

Field'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: Field msg -> Struct msg Source #

FromStruct msg (Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Field ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

ListElem mut (Field mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Field mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Field mut)) Source #

toUntypedList :: List mut (Field mut) -> List mut Source #

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

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

MessageDefault (Field mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (Field mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Field mut -> Message mut Source #

newtype List mut (Field mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Field mut) = Field'List_ (ListOf mut (Struct mut))

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

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

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

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

set_Field'codeOrder :: RWCtx m s => Field (Mut s) -> Word16 -> 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 #

data Field' (mut :: Mutability) Source #

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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'unknown' :: RWCtx m s => Field (Mut s) -> Word16 -> m () Source #

newtype Field'slot msg Source #

Constructors

Field'slot'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Field'slot mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Field'slot mut) Source #

HasMessage (Field'slot mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Field'slot mut -> Message mut 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 #

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 #

newtype Field'group msg Source #

Constructors

Field'group'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Field'group mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Field'group mut -> Message mut Source #

newtype Field'ordinal msg Source #

Constructors

Field'ordinal'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Field'ordinal mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Field'ordinal mut -> Message mut Source #

data Field'ordinal' (mut :: Mutability) Source #

Instances

Instances details
FromStruct mut (Field'ordinal' mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newtype Enumerant msg Source #

Constructors

Enumerant'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: Enumerant msg -> Struct msg Source #

FromStruct msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Enumerant ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Enumerant msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (Enumerant ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Enumerant ('Mut s)) Source #

MutListElem s (Enumerant ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Enumerant ('Mut s))) Source #

ListElem mut (Enumerant mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Enumerant mut) Source #

Methods

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 # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (Enumerant mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Enumerant mut -> Message mut Source #

newtype List mut (Enumerant mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Enumerant mut) = Enumerant'List_ (ListOf mut (Struct mut))

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 #

new_Enumerant'name :: RWCtx m s => Int -> Enumerant (Mut s) -> m (Text (Mut s)) 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 #

newtype Superclass msg Source #

Constructors

Superclass'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: Superclass msg -> Struct msg Source #

FromStruct msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Superclass ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Superclass msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (Superclass ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Superclass ('Mut s)) Source #

MutListElem s (Superclass ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Superclass ('Mut s))) Source #

ListElem mut (Superclass mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Superclass mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Superclass mut)) Source #

toUntypedList :: List mut (Superclass mut) -> List mut Source #

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

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

MessageDefault (Superclass mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (Superclass mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Superclass mut -> Message mut Source #

newtype List mut (Superclass mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Superclass mut) = Superclass'List_ (ListOf mut (Struct mut))

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 #

newtype Method msg Source #

Constructors

Method'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: Method msg -> Struct msg Source #

FromStruct msg (Method msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Method ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Method msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (Method ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Method ('Mut s)) Source #

MutListElem s (Method ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Method ('Mut s))) Source #

ListElem mut (Method mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Method mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Method mut)) Source #

toUntypedList :: List mut (Method mut) -> List mut Source #

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

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

MessageDefault (Method mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (Method mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Method mut -> Message mut Source #

newtype List mut (Method mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Method mut) = Method'List_ (ListOf mut (Struct mut))

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

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

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

new_Method'name :: RWCtx m s => Int -> Method (Mut s) -> m (Text (Mut s)) 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 #

newtype Type msg Source #

Constructors

Type'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: Type msg -> Struct msg Source #

FromStruct msg (Type msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Type ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Type msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (Type ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Type ('Mut s)) Source #

MutListElem s (Type ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

ListElem mut (Type mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Type mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Type mut)) Source #

toUntypedList :: List mut (Type mut) -> List mut Source #

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

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

MessageDefault (Type mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (Type mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Type mut -> Message mut Source #

newtype List mut (Type mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Type mut) = Type'List_ (ListOf mut (Struct mut))

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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

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'unknown' :: RWCtx m s => Type (Mut s) -> Word16 -> m () Source #

newtype Type'list msg Source #

Constructors

Type'list'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Type'list mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Type'list mut) Source #

HasMessage (Type'list mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Type'list mut -> Message 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 #

Constructors

Type'enum'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Type'enum mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Type'enum mut) Source #

HasMessage (Type'enum mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Type'enum mut -> Message 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 #

Constructors

Type'struct'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Type'struct mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Type'struct mut) Source #

HasMessage (Type'struct mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Type'struct mut -> Message mut 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 #

newtype Type'interface msg Source #

Constructors

Type'interface'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Type'interface mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Type'interface mut) Source #

HasMessage (Type'interface mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Type'interface mut -> Message mut 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 #

newtype Type'anyPointer msg Source #

Constructors

Type'anyPointer'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Type'anyPointer mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Type'anyPointer mut -> Message mut Source #

newtype Type'anyPointer'parameter msg Source #

Instances

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

MessageDefault (Type'anyPointer'parameter mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

HasMessage (Type'anyPointer'parameter mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype Brand msg Source #

Constructors

Brand'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: Brand msg -> Struct msg Source #

FromStruct msg (Brand msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Brand ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Brand msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (Brand ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Brand ('Mut s)) Source #

MutListElem s (Brand ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

ListElem mut (Brand mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Brand mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Brand mut)) Source #

toUntypedList :: List mut (Brand mut) -> List mut Source #

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

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

MessageDefault (Brand mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (Brand mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Brand mut -> Message mut Source #

newtype List mut (Brand mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Brand mut) = Brand'List_ (ListOf mut (Struct mut))

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 #

has_Brand'scopes :: ReadCtx m msg => Brand msg -> m Bool 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 #

Constructors

Brand'Scope'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Brand'Scope ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Brand'Scope mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Brand'Scope mut)) Source #

toUntypedList :: List mut (Brand'Scope mut) -> List mut Source #

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Brand'Scope mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Brand'Scope mut -> Message mut Source #

newtype List mut (Brand'Scope mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Brand'Scope mut) = Brand'Scope'List_ (ListOf mut (Struct mut))

data Brand'Scope' (mut :: Mutability) Source #

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

fromStruct :: ReadCtx m mut => Struct mut -> m (Brand'Scope' mut) 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 #

newtype Brand'Binding msg Source #

Constructors

Brand'Binding'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Brand'Binding ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Brand'Binding mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Brand'Binding mut)) Source #

toUntypedList :: List mut (Brand'Binding mut) -> List mut Source #

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

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

messageDefault :: ReadCtx m mut => Message mut -> m (Brand'Binding mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Brand'Binding mut -> Message mut Source #

newtype List mut (Brand'Binding mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Brand'Binding mut) = Brand'Binding'List_ (ListOf mut (Struct mut))

data Brand'Binding' (mut :: Mutability) Source #

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

set_Brand'Binding'type_ :: (RWCtx m s, ToPtr s (Type (Mut s))) => Brand'Binding (Mut s) -> Type (Mut s) -> m () Source #

newtype Value msg Source #

Constructors

Value'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: Value msg -> Struct msg Source #

FromStruct msg (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Value ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (Value ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Value ('Mut s)) Source #

MutListElem s (Value ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Value ('Mut s))) Source #

ListElem mut (Value mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Value mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Value mut)) Source #

toUntypedList :: List mut (Value mut) -> List mut Source #

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

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

MessageDefault (Value mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (Value mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Value mut -> Message mut Source #

newtype List mut (Value mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Value mut) = Value'List_ (ListOf mut (Struct mut))

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

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

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

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

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

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

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

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

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

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

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

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

set_Value'float64 :: RWCtx m s => Value (Mut s) -> Double -> m () 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'enum :: RWCtx m s => Value (Mut s) -> Word16 -> 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'interface :: RWCtx m s => Value (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 #

set_Value'unknown' :: RWCtx m s => Value (Mut s) -> Word16 -> m () Source #

newtype Annotation msg Source #

Constructors

Annotation'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: Annotation msg -> Struct msg Source #

FromStruct msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (Annotation ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (Annotation msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (Annotation ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (Annotation ('Mut s)) Source #

MutListElem s (Annotation ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (Annotation ('Mut s))) Source #

ListElem mut (Annotation mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (Annotation mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (Annotation mut)) Source #

toUntypedList :: List mut (Annotation mut) -> List mut Source #

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

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

MessageDefault (Annotation mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (Annotation mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: Annotation mut -> Message mut Source #

newtype List mut (Annotation mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (Annotation mut) = Annotation'List_ (ListOf mut (Struct mut))

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 #

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 #

data ElementSize Source #

Instances

Instances details
Enum ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Eq ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Read ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Show ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Generic ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

type Rep ElementSize :: Type -> Type #

Decerialize ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

Associated Types

type Cerial mut ElementSize Source #

IsWord ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Cerialize s ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => Message ('Mut s) -> ElementSize -> m (Cerial ('Mut s) ElementSize) Source #

MutListElem s ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) ElementSize) Source #

ListElem mut ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut ElementSize Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut ElementSize) Source #

toUntypedList :: List mut ElementSize -> List mut Source #

length :: List mut ElementSize -> Int Source #

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

Cerialize s (Vector (Vector (Vector (Vector (Vector (Vector ElementSize)))))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

Cerialize s (Vector (Vector (Vector (Vector (Vector ElementSize))))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

Cerialize s (Vector (Vector (Vector (Vector ElementSize)))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

Cerialize s (Vector (Vector (Vector ElementSize))) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

Cerialize s (Vector (Vector ElementSize)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

Cerialize s (Vector ElementSize) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema.Pure

Methods

cerialize :: RWCtx m s => Message ('Mut s) -> Vector ElementSize -> m (Cerial ('Mut s) (Vector ElementSize)) Source #

type Rep ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema.Pure

newtype List mut ElementSize Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype CapnpVersion msg Source #

Constructors

CapnpVersion'newtype_ (Struct msg) 

Instances

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

Defined in Capnp.Gen.Capnp.Schema

Methods

toStruct :: CapnpVersion msg -> Struct msg Source #

FromStruct msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (CapnpVersion ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (CapnpVersion msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (CapnpVersion ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (CapnpVersion ('Mut s)) Source #

MutListElem s (CapnpVersion ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (CapnpVersion ('Mut s))) Source #

ListElem mut (CapnpVersion mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (CapnpVersion mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (CapnpVersion mut)) Source #

toUntypedList :: List mut (CapnpVersion mut) -> List mut Source #

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

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

MessageDefault (CapnpVersion mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (CapnpVersion mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

message :: CapnpVersion mut -> Message mut Source #

newtype List mut (CapnpVersion mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (CapnpVersion mut) = CapnpVersion'List_ (ListOf mut (Struct mut))

newtype CodeGeneratorRequest msg Source #

Instances

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

Defined in Capnp.Gen.Capnp.Schema

FromStruct msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

ToPtr s (CodeGeneratorRequest ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

FromPtr msg (CodeGeneratorRequest msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

Allocate s (CodeGeneratorRequest ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

new :: WriteCtx m s => Message ('Mut s) -> m (CodeGeneratorRequest ('Mut s)) Source #

MutListElem s (CodeGeneratorRequest ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

setIndex :: RWCtx m s => CodeGeneratorRequest ('Mut s) -> Int -> List ('Mut s) (CodeGeneratorRequest ('Mut s)) -> m () Source #

newList :: WriteCtx m s => Message ('Mut s) -> Int -> m (List ('Mut s) (CodeGeneratorRequest ('Mut s))) Source #

ListElem mut (CodeGeneratorRequest mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (CodeGeneratorRequest mut) Source #

Methods

listFromPtr :: ReadCtx m mut => Message mut -> Maybe (Ptr mut) -> m (List mut (CodeGeneratorRequest mut)) Source #

toUntypedList :: List mut (CodeGeneratorRequest mut) -> List mut Source #

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

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

MessageDefault (CodeGeneratorRequest mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

HasMessage (CodeGeneratorRequest mut) mut Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (CodeGeneratorRequest mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

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 #

newtype CodeGeneratorRequest'RequestedFile msg Source #

Instances

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

ToPtr s (CodeGeneratorRequest'RequestedFile ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

Methods

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

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

Associated Types

data List mut (CodeGeneratorRequest'RequestedFile mut) Source #

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (CodeGeneratorRequest'RequestedFile mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

newtype CodeGeneratorRequest'RequestedFile'Import msg Source #

Instances

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

ToPtr s (CodeGeneratorRequest'RequestedFile'Import ('Mut s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

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

Defined in Capnp.Gen.Capnp.Schema

newtype List mut (CodeGeneratorRequest'RequestedFile'Import mut) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Schema