capnp-0.7.0.0: Cap'n Proto for Haskell

Safe HaskellNone
LanguageHaskell2010

Capnp.Gen.Capnp.Compat.Json

Documentation

newtype Value msg Source #

Constructors

Value'newtype_ (Struct msg) 
Instances
TraverseMsg Value Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Value msgA -> m (Value msgB) Source #

ToStruct msg (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

toStruct :: Value msg -> Struct msg Source #

FromStruct msg (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

toPtr :: WriteCtx m s => MutMsg s -> Value (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

FromPtr msg (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

ListElem msg (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

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

Methods

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

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

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

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

MessageDefault (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

messageDefault :: InMessage (Value msg) -> Value msg Source #

HasMessage (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

type InMessage (Value msg) :: Type Source #

Methods

message :: Value msg -> InMessage (Value msg) Source #

newtype List msg (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

newtype List msg (Value msg) = Value'List_ (ListOf msg (Struct msg))
type InMessage (Value msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type InMessage (Value msg) = msg

data Value' msg Source #

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

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

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

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

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

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

set_Value'object :: RWCtx m s => Value (MutMsg s) -> List (MutMsg s) (Value'Field (MutMsg s)) -> m () Source #

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

newtype Value'Field msg Source #

Constructors

Value'Field'newtype_ (Struct msg) 
Instances
TraverseMsg Value'Field Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Value'Field msgA -> m (Value'Field msgB) Source #

ToStruct msg (Value'Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

ToPtr s (Value'Field (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

FromPtr msg (Value'Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

data List msg (Value'Field msg) :: Type Source #

Methods

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

toUntypedList :: List msg (Value'Field msg) -> List msg Source #

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

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

MessageDefault (Value'Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

HasMessage (Value'Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

type InMessage (Value'Field msg) :: Type Source #

newtype List msg (Value'Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

newtype List msg (Value'Field msg) = Value'Field'List_ (ListOf msg (Struct msg))
type InMessage (Value'Field msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type InMessage (Value'Field msg) = msg

newtype Value'Call msg Source #

Constructors

Value'Call'newtype_ (Struct msg) 
Instances
TraverseMsg Value'Call Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> Value'Call msgA -> m (Value'Call msgB) Source #

ToStruct msg (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

toStruct :: Value'Call msg -> Struct msg Source #

FromStruct msg (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

ToPtr s (Value'Call (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

FromPtr msg (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

ListElem msg (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

data List msg (Value'Call msg) :: Type Source #

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (Value'Call msg)) Source #

toUntypedList :: List msg (Value'Call msg) -> List msg Source #

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

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

MessageDefault (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

HasMessage (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

type InMessage (Value'Call msg) :: Type Source #

newtype List msg (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

newtype List msg (Value'Call msg) = Value'Call'List_ (ListOf msg (Struct msg))
type InMessage (Value'Call msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type InMessage (Value'Call msg) = msg

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

newtype FlattenOptions msg Source #

Constructors

FlattenOptions'newtype_ (Struct msg) 
Instances
TraverseMsg FlattenOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> FlattenOptions msgA -> m (FlattenOptions msgB) Source #

ToStruct msg (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

toStruct :: FlattenOptions msg -> Struct msg Source #

FromStruct msg (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

ToPtr s (FlattenOptions (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

toPtr :: WriteCtx m s => MutMsg s -> FlattenOptions (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

FromPtr msg (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

ListElem msg (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (FlattenOptions msg)) Source #

toUntypedList :: List msg (FlattenOptions msg) -> List msg Source #

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

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

MessageDefault (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

HasMessage (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

type InMessage (FlattenOptions msg) :: Type Source #

newtype List msg (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

newtype List msg (FlattenOptions msg) = FlattenOptions'List_ (ListOf msg (Struct msg))
type InMessage (FlattenOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type InMessage (FlattenOptions msg) = msg

newtype DiscriminatorOptions msg Source #

Instances
TraverseMsg DiscriminatorOptions Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

tMsg :: Applicative m => (msgA -> m msgB) -> DiscriminatorOptions msgA -> m (DiscriminatorOptions msgB) Source #

ToStruct msg (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

FromStruct msg (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

ToPtr s (DiscriminatorOptions (MutMsg s)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

toPtr :: WriteCtx m s => MutMsg s -> DiscriminatorOptions (MutMsg s) -> m (Maybe (Ptr (MutMsg s))) Source #

FromPtr msg (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

Methods

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

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

Defined in Capnp.Gen.Capnp.Compat.Json

ListElem msg (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

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

Methods

listFromPtr :: ReadCtx m msg => msg -> Maybe (Ptr msg) -> m (List msg (DiscriminatorOptions msg)) Source #

toUntypedList :: List msg (DiscriminatorOptions msg) -> List msg Source #

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

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

MessageDefault (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

HasMessage (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

Associated Types

type InMessage (DiscriminatorOptions msg) :: Type Source #

newtype List msg (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json

type InMessage (DiscriminatorOptions msg) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Compat.Json