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

Capnp.Repr.Methods

Description

 
Synopsis

Documentation

data Method c p r Source #

Represents a method on the interface type c with parameter type p and return type r.

Constructors

Method 

Instances

Instances details
HasMethod name c p r => IsLabel name (Method c p r) Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

fromLabel :: Method c p r #

class (IsCap c, IsStruct p, IsStruct r) => HasMethod (name :: Symbol) c p r | name c -> p r where Source #

An instance HasMethod name c p r indicates that the interface type c has a method named name with parameter type p and return type r. The generated code includes instances of this for each method in the schema.

Methods

methodByLabel :: Method c p r Source #

Instances

Instances details
(TypeParam sturdyRef, TypeParam owner) => HasMethod "save" (Persistent sturdyRef owner) (Persistent'SaveParams sturdyRef owner) (Persistent'SaveResults sturdyRef owner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

methodByLabel :: Method (Persistent sturdyRef owner) (Persistent'SaveParams sturdyRef owner) (Persistent'SaveResults sturdyRef owner) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasMethod "export" (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults externalRef externalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

methodByLabel :: Method (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'export'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults externalRef externalOwner) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => HasMethod "import_" (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults internalRef internalOwner) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

methodByLabel :: Method (RealmGateway internalRef externalRef internalOwner externalOwner) (RealmGateway'import'params internalRef externalRef internalOwner externalOwner) (Persistent'SaveResults internalRef internalOwner) Source #

newtype Pipeline a Source #

A Pipeline a is a reference to possibly-not-resolved result from a method call.

Constructors

Pipeline Pipeline 

Instances

Instances details
AsClient Pipeline Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

asClient :: (MonadSTM m, IsCap c) => Pipeline c -> m (Client c) Source #

newtype Client a Source #

Constructors

Client Client 

Instances

Instances details
AsClient Client Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

asClient :: (MonadSTM m, IsCap c) => Client c -> m (Client c) Source #

Eq (Client a) Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

(==) :: Client a -> Client a -> Bool #

(/=) :: Client a -> Client a -> Bool #

Show (Client a) Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

showsPrec :: Int -> Client a -> ShowS #

show :: Client a -> String #

showList :: [Client a] -> ShowS #

ReprFor a ~ 'Ptr ('Just 'Cap) => IsClient (Client a) Source # 
Instance details

Defined in Capnp.Repr.Methods

(TypeParam sturdyRef, TypeParam owner) => Parse (Persistent sturdyRef owner) (Client (Persistent sturdyRef owner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (Persistent sturdyRef owner) -> m (Client (Persistent sturdyRef owner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Client (Persistent sturdyRef owner) -> m (Raw ('Mut s) (Persistent sturdyRef owner)) Source #

(TypeParam internalRef, TypeParam externalRef, TypeParam internalOwner, TypeParam externalOwner) => Parse (RealmGateway internalRef externalRef internalOwner externalOwner) (Client (RealmGateway internalRef externalRef internalOwner externalOwner)) Source # 
Instance details

Defined in Capnp.Gen.Capnp.Persistent.New

Methods

parse :: ReadCtx m 'Const => Raw 'Const (RealmGateway internalRef externalRef internalOwner externalOwner) -> m (Client (RealmGateway internalRef externalRef internalOwner externalOwner)) Source #

encode :: RWCtx m s => Message ('Mut s) -> Client (RealmGateway internalRef externalRef internalOwner externalOwner) -> m (Raw ('Mut s) (RealmGateway internalRef externalRef internalOwner externalOwner)) Source #

pipe :: (IsStruct a, ReprFor b ~ 'Ptr pr) => Field k a b -> Pipeline a -> Pipeline b Source #

Project a pipeline to a struct onto one of its pointer fields.

pipelineClient :: (IsCap a, MonadSTM m) => Pipeline a -> m (Client a) Source #

Convert a Pipeline for a capability into a Client.

waitPipeline :: forall a m pr. ('Ptr pr ~ ReprFor a, IsPtrRepr pr, MonadSTM m) => Pipeline a -> m (Raw 'Const a) Source #

Wait for the result of a pipeline, and return its value.

class AsClient f where Source #

The AsClient class allows callers of rpc methods to abstract over Clients and Pipelines. asClient converts either of those to a client so that methods can be invoked on it.

Methods

asClient :: MonadSTM m => IsCap c => f c -> m (Client c) Source #

Instances

Instances details
AsClient Client Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

asClient :: (MonadSTM m, IsCap c) => Client c -> m (Client c) Source #

AsClient Pipeline Source # 
Instance details

Defined in Capnp.Repr.Methods

Methods

asClient :: (MonadSTM m, IsCap c) => Pipeline c -> m (Client c) Source #

Calling methods.

callB :: (AsClient f, IsCap c, IsStruct p, MonadSTM m) => Method c p r -> (forall s. PureBuilder s (Raw ('Mut s) p)) -> f c -> m (Pipeline r) Source #

Call a method. Use the provided PureBuilder to construct the parameters.

callR :: (AsClient f, IsCap c, IsStruct p, MonadSTM m) => Method c p r -> Raw 'Const p -> f c -> m (Pipeline r) Source #

Call a method, supplying the parameters as a Raw struct.

callP :: forall c p r f m pp. (AsClient f, IsCap c, IsStruct p, Parse p pp, MonadSTM m, MonadThrow m) => Method c p r -> pp -> f c -> m (Pipeline r) Source #

Call a method, supplying the parmaeters in parsed form.