Safe Haskell | Safe-Inferred |
---|---|
Language | GHC2021 |
Choreography.Choreography
Description
Operations for writing choreographies.
Synopsis
- locally :: KnownSymbol (l :: LocTy) => Member l ps -> (Unwrap l -> m a) -> Choreo ps m (Located '[l] a)
- congruently :: forall ls a ps m. KnownSymbols ls => Subset ls ps -> (Unwraps ls -> a) -> Choreo ps m (Located ls a)
- naked :: KnownSymbols ps => Subset ps qs -> Located qs a -> Choreo ps m a
- class KnownSymbol loc => CanSend struct loc val owners census | struct -> loc val owners census where
- presentToSend :: struct -> Member loc census
- ownsMessagePayload :: struct -> Member loc owners
- structMessagePayload :: struct -> Located owners val
- broadcast :: forall l a ps ls m s. (Show a, Read a, KnownSymbol l, KnownSymbols ps, CanSend s l a ls ps) => s -> Choreo ps m a
- (~>) :: (Show a, Read a, KnownSymbol l, KnownSymbols ls', CanSend s l a ls ps) => s -> Subset ls' ps -> Choreo ps m (Located ls' a)
- conclaveToAll :: forall ls a ps m. KnownSymbols ls => Subset ls ps -> Choreo ls m (Located ls a) -> Choreo ps m (Located ls a)
- conclaveTo :: forall ls a rs ps m. KnownSymbols ls => Subset ls ps -> Subset rs ls -> Choreo ls m (Located rs a) -> Choreo ps m (Located rs a)
Computation per se
Arguments
:: KnownSymbol (l :: LocTy) | |
=> Member l ps | Location performing the local computation. |
-> (Unwrap l -> m a) | The local computation, which can use a constrained unwrap function. |
-> Choreo ps m (Located '[l] a) |
Perform a local computation at a given location.
congruently :: forall ls a ps m. KnownSymbols ls => Subset ls ps -> (Unwraps ls -> a) -> Choreo ps m (Located ls a) infix 4 Source #
Perform the exact same pure computation in replicate at multiple locations. The computation can not use anything local to an individual party, including their identity.
naked :: KnownSymbols ps => Subset ps qs -> Located qs a -> Choreo ps m a Source #
Unwrap a value known to the entire census.
Communication
class KnownSymbol loc => CanSend struct loc val owners census | struct -> loc val owners census where Source #
Writing out the first argument to ~>
can be done a few different ways depending on context, represented by this class.
Methods
presentToSend :: struct -> Member loc census Source #
ownsMessagePayload :: struct -> Member loc owners Source #
structMessagePayload :: struct -> Located owners val Source #
Instances
(KnownSymbol l, ExplicitMember l ls) => CanSend (Member l ps, Located ls a) l a ls ps Source # | |
Defined in Choreography.Choreography | |
KnownSymbol l => CanSend (Member l ps, (Member l ls, Located ls a)) l a ls ps Source # | |
Defined in Choreography.Choreography | |
KnownSymbol l => CanSend (Member l ls, Subset ls ps, Located ls a) l a ls ps Source # | |
Defined in Choreography.Choreography |
broadcast :: forall l a ps ls m s. (Show a, Read a, KnownSymbol l, KnownSymbols ps, CanSend s l a ls ps) => s -> Choreo ps m a Source #
Send a value from one party to the entire census.
Arguments
:: (Show a, Read a, KnownSymbol l, KnownSymbols ls', CanSend s l a ls ps) | |
=> s | The message argument can take three forms: (Member sender census, wrapped owners a) -- where sender is explicitly listed in owners (Member sender owners, Subset owners census, wrapped owners a) (Member sender census, (Member sender owners, wrapped owners a) |
-> Subset ls' ps | The recipients. |
-> Choreo ps m (Located ls' a) |
Communication between a sender and a list of receivers.
Conclaves
conclaveToAll :: forall ls a ps m. KnownSymbols ls => Subset ls ps -> Choreo ls m (Located ls a) -> Choreo ps m (Located ls a) infix 4 Source #
Lift a choreography involving fewer parties into the larger party space. This version, where the returned value is Located at the entire conclave, does not add a Located layer.
conclaveTo :: forall ls a rs ps m. KnownSymbols ls => Subset ls ps -> Subset rs ls -> Choreo ls m (Located rs a) -> Choreo ps m (Located rs a) infix 4 Source #
Lift a choreography of involving fewer parties into the larger party space. This version, where the returned value is already Located, does not add a Located layer.