| Safe Haskell | None |
|---|---|
| Language | GHC2021 |
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
- type LocTm = String
- type LocTy = Symbol
- data a @ (l :: LocTy)
- mkLoc :: String -> Q [Dec]
- type Choreo (m :: Type -> Type) = Freer (ChoreoSig m)
- locally :: forall (l :: Symbol) m a. KnownSymbol l => Proxy l -> (Unwrap l -> m a) -> Choreo m (a @ l)
- (~>) :: forall a (l :: Symbol) (l' :: Symbol) (m :: Type -> Type). (Show a, Read a, KnownSymbol l, KnownSymbol l') => (Proxy l, a @ l) -> Proxy l' -> Choreo m (a @ l')
- (~~>) :: forall a (l :: Symbol) (l' :: Symbol) m. (Show a, Read a, KnownSymbol l, KnownSymbol l') => (Proxy l, Unwrap l -> m a) -> Proxy l' -> Choreo m (a @ l')
- cond :: forall a (l :: Symbol) (m :: Type -> Type) b. (Show a, Read a, KnownSymbol l) => (Proxy l, a @ l) -> (a -> Choreo m b) -> Choreo m b
- cond' :: forall a (l :: Symbol) m b. (Show a, Read a, KnownSymbol l) => (Proxy l, Unwrap l -> m a) -> (a -> Choreo m b) -> Choreo m b
- cond_ :: forall a (l :: Symbol) (m :: Type -> Type) b. (Bounded a, Enum a, Show a, Read a, KnownSymbol l) => (Proxy l, a @ l) -> (a -> Choreo m (b @ l)) -> Choreo m (b @ l)
- cond_' :: forall a (l :: Symbol) m b. (Bounded a, Enum a, Show a, Read a, KnownSymbol l) => (Proxy l, Unwrap l -> m a) -> (a -> Choreo m (b @ l)) -> Choreo m (b @ l)
- type Host = String
- type Port = Int
- data HttpConfig
- mkHttpConfig :: [(LocTm, (Host, Port))] -> HttpConfig
- runChoreo :: Monad m => Choreo m a -> m a
- runChoreography :: (Backend config, MonadIO m) => config -> Choreo m a -> LocTm -> m a
Locations and Located Values
The Choreo monad
Choreo operations
Arguments
| :: forall (l :: Symbol) m a. 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.
Arguments
| :: forall a (l :: Symbol) (l' :: Symbol) (m :: Type -> Type). (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.
Arguments
| :: forall a (l :: Symbol) (l' :: Symbol) m. (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.
Arguments
| :: forall a (l :: Symbol) (m :: Type -> Type) b. (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.
Arguments
| :: forall a (l :: Symbol) m b. (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.
Arguments
| :: forall a (l :: Symbol) (m :: Type -> Type) b. (Bounded a, Enum a, 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 @ l)) | A function that describes the follow-up choreographies based on the value of scrutinee. |
| -> Choreo m (b @ l) |
Conditionally execute choreographies at participating locations, based on a located value.
Arguments
| :: forall a (l :: Symbol) m b. (Bounded a, Enum a, 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 @ l)) | A function that describes the follow-up choreographies based on the result of the local computation. |
| -> Choreo m (b @ l) |
A variant of cond_ that conditonally executes choregraphies at participating locations,
based on the result of a local computation.
Message transport backends
The HTTP backend
data HttpConfig Source #
The HTTP backend configuration specifies how locations are mapped to network hosts and ports.
Instances
| Backend HttpConfig Source # | |
Defined in Choreography.Network.Http Methods locs :: HttpConfig -> [LocTm] Source # 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.