extensible-effects-concurrent-0.23.0: Message passing concurrency as extensible-effect

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Api

Description

This module contains a mechanism to specify what kind of messages (aka requests) a Server (Process) can handle, and if the caller blocks and waits for an answer, which the server process provides.

The type magic in the Api type family allows to define a related set of requests along with the corresponding responses.

Request handling can be either blocking, if a response is required, or non-blocking.

A process can serve a specific Api instance by using the functions provided by the Control.Eff.Concurrent.Api.Server module.

To enable a process to use such a service, the functions provided by the Control.Eff.Concurrent.Api.Client should be used.

Synopsis

Documentation

data family Api (api :: Type) (reply :: Synchronicity) Source #

This data family defines an API, a communication interface description between at least two processes. The processes act as servers or client(s) regarding a specific instance of this type.

The first parameter is usually a user defined phantom type that identifies the Api instance.

The second parameter specifies if a specific constructor of an (GADT-like) Api instance is Synchronous, i.e. returns a result and blocks the caller or if it is Asynchronous

Also, for better logging, the an instance of ToPretty for the Api index type must be given.

Example:

data BookShop deriving Typeable

data instance Api BookShop r where
  RentBook  :: BookId   -> Api BookShop ('Synchronous (Either RentalError RentalId))
  BringBack :: RentalId -> Api BookShop 'Asynchronous

type instance ToPretty BookShop = PutStr "book shop"

type BookId = Int
type RentalId = Int
type RentalError = String
Instances
Show i => Show (Api (Sup i o) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

showsPrec :: Int -> Api (Sup i o) (Synchronous r) -> ShowS #

show :: Api (Sup i o) (Synchronous r) -> String #

showList :: [Api (Sup i o) (Synchronous r)] -> ShowS #

NFData i => NFData (Api (Sup i o) (Synchronous r)) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

Methods

rnf :: Api (Sup i o) (Synchronous r) -> () #

NFData (Api (ObserverRegistry o) r) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Observer

Methods

rnf :: Api (ObserverRegistry o) r -> () #

NFData o => NFData (Api (Observer o) Asynchronous) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.Observer

Methods

rnf :: Api (Observer o) Asynchronous -> () #

data Api (Observer o) r Source #

A minimal Api for handling observations. This is one simple way of receiving observations - of course users can use any other Asynchronous Api message type for receiving observations.

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Api.Observer

data Api (Observer o) r where
type ToPretty (Api x y :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api

type ToPretty (Api x y :: Type) = PrettySurrounded (PutStr "<") (PutStr ">") (("API" <:> ToPretty x) <+> ToPretty y)
data Api (SomeMessage a) s Source # 
Instance details

Defined in Control.Eff.Concurrent.Api.GenServer

data Api (SomeMessage a) s where
data Api (ObserverRegistry o) r Source #

Api for managing observers. This can be added to any server for any number of different observation types. The functions manageObservers and handleObserverRegistration are used to include observer handling;

Since: 0.16.0

Instance details

Defined in Control.Eff.Concurrent.Api.Observer

data Api (ObserverRegistry o) r where
data Api (Sup i o) r Source #

The Api instance contains methods to start, stop and lookup a child process, as well as a diagnostic callback.

Since: 0.23.0

Instance details

Defined in Control.Eff.Concurrent.Api.Supervisor

data Api (Sup i o) r where

data Synchronicity Source #

The (promoted) constructors of this type specify (at the type level) the reply behavior of a specific constructor of an Api instance.

Constructors

Synchronous Type

Specify that handling a request is a blocking operation with a specific return type, e.g. ('Synchronous (Either RentalError RentalId))

Asynchronous

Non-blocking, asynchronous, request handling

type Tangible i = (NFData i, Typeable i, Show i, PrettyTypeShow (ToPretty i)) Source #

A set of constraints for types that can evaluated via NFData, compared via Ord and presented dynamically via Typeable, and represented both as values via Show, as well as on the type level via ToPretty.

newtype Server api Source #

This is a tag-type that wraps around a ProcessId and holds an Api index type.

Constructors

Server 
Instances
Eq (Server api) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api

Methods

(==) :: Server api -> Server api -> Bool #

(/=) :: Server api -> Server api -> Bool #

Ord (Server api) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api

Methods

compare :: Server api -> Server api -> Ordering #

(<) :: Server api -> Server api -> Bool #

(<=) :: Server api -> Server api -> Bool #

(>) :: Server api -> Server api -> Bool #

(>=) :: Server api -> Server api -> Bool #

max :: Server api -> Server api -> Server api #

min :: Server api -> Server api -> Server api #

PrettyTypeShow (ToPretty api) => Show (Server api) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api

Methods

showsPrec :: Int -> Server api -> ShowS #

show :: Server api -> String #

showList :: [Server api] -> ShowS #

NFData (Server api) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api

Methods

rnf :: Server api -> () #

type ToPretty (Server a :: Type) Source # 
Instance details

Defined in Control.Eff.Concurrent.Api

type ToPretty (Server a :: Type) = ToPretty a <+> PutStr "server"

fromServer :: forall api api. Iso (Server api) (Server api) ProcessId ProcessId Source #

proxyAsServer :: proxy api -> ProcessId -> Server api Source #

Tag a ProcessId with an Api type index to mark it a Server process handling that API

asServer :: forall api. ProcessId -> Server api Source #

Tag a ProcessId with an Api type index to mark it a Server process handling that API