extensible-effects-concurrent-0.18.1: 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 familiy allows to define a related set of requests along with the corresponding responses.

Request handling can be either blocking, if a response is requred, 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

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 BookId = Int
type RentalId = Int
type RentalError = String
Instances
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
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 handleObserverApi 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 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

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 #

Typeable 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 #

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