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

Safe HaskellNone
LanguageHaskell2010

Control.Eff.Concurrent.Api

Description

This module contains a mechanisms to specify what kind of messages a process can receive and possible answer by sending a message back to the orginator.

A message can be either a blocking or a non-blocking request.

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

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 to processes, where one process acts as a server and the other(s) as client(s).

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

data Synchronicity Source #

This data kind is used to indicate at the type level if a specific constructor of an Api instance has a result for which some caller has to wait, or if it is asynchronous.

Constructors

Synchronous Type

Blocking operation with a specific return type, e.g. ('Synchronous (Either RentalError RentalId))

Asynchronous

Non-blocking async operation

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 k api) Source # 

Methods

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

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

Ord (Server k api) Source # 

Methods

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

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

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

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

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

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

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

Read (Server k api) Source # 

Methods

readsPrec :: Int -> ReadS (Server k api) #

readList :: ReadS [Server k api] #

readPrec :: ReadPrec (Server k api) #

readListPrec :: ReadPrec [Server k api] #

Typeable k api => Show (Server k api) Source # 

Methods

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

show :: Server k api -> String #

showList :: [Server k 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