HasChor-0.1.0.1: Functional choreographic programming in Haskell
Safe HaskellSafe-Inferred
LanguageGHC2021

Choreography

Description

This module defines the interface to HasChor. The client of the library is highly recommended to only use constructs exported by this module.

Synopsis

Locations and Located Values

type LocTm = String Source #

Term-level locations.

type LocTy = Symbol Source #

Type-level locations.

data a @ (l :: LocTy) Source #

Located values.

a @ l represents a value of type a at location l.

mkLoc :: String -> Q [Dec] Source #

Define a location at both type and term levels.

The Choreo monad

type Choreo m = Freer (ChoreoSig m) Source #

Monad for writing choreographies.

Choreo operations

locally Source #

Arguments

:: KnownSymbol l 
=> Proxy l

Location performing the local computation.

-> (Unwrap l -> m a)

The local computation given a constrained unwrap funciton.

-> Choreo m (a @ l) 

Perform a local computation at a given location.

(~>) Source #

Arguments

:: (Show a, Read a, KnownSymbol l, KnownSymbol l') 
=> (Proxy l, a @ l)

A pair of a sender's location and a value located at the sender

-> Proxy l'

A receiver's location.

-> Choreo m (a @ l') 

Communication between a sender and a receiver.

(~~>) Source #

Arguments

:: (Show a, Read a, KnownSymbol l, KnownSymbol l') 
=> (Proxy l, Unwrap l -> m a)

A pair of a sender's location and a local computation.

-> Proxy l'

A receiver's location.

-> Choreo m (a @ l') 

A variant of ~> that sends the result of a local computation.

cond Source #

Arguments

:: (Show a, Read a, KnownSymbol l) 
=> (Proxy l, a @ l)

A pair of a location and a scrutinee located on it.

-> (a -> Choreo m b)

A function that describes the follow-up choreographies based on the value of scrutinee.

-> Choreo m b 

Conditionally execute choreographies based on a located value.

cond' Source #

Arguments

:: (Show a, Read a, KnownSymbol l) 
=> (Proxy l, Unwrap l -> m a)

A pair of a location and a local computation.

-> (a -> Choreo m b)

A function that describes the follow-up choreographies based on the result of the local computation.

-> Choreo m b 

A variant of cond that conditonally executes choregraphies based on the result of a local computation.

Message transport backends

The HTTP backend

type Port = Int Source #

data HttpConfig Source #

The HTTP backend configuration specifies how locations are mapped to network hosts and ports.

Instances

Instances details
Backend HttpConfig Source # 
Instance details

Defined in Choreography.Network.Http

Methods

runNetwork :: MonadIO m => HttpConfig -> LocTm -> Network m a -> m a Source #

mkHttpConfig :: [(LocTm, (Host, Port))] -> HttpConfig Source #

Create a HTTP backend configuration from a association list that maps locations to network hosts and ports.

Running choreographies

runChoreo :: Monad m => Choreo m a -> m a Source #

Run a Choreo monad directly.

runChoreography :: (Backend config, MonadIO m) => config -> Choreo m a -> LocTm -> m a Source #

Run a choreography with a message transport backend.