cloudchor
Safe HaskellNone
LanguageGHC2021

Choreography.Location.Multi

Description

This module defines multiply-located values and combinators for manipulating them.

Synopsis

Documentation

type (@@) a (ls :: [LocTy]) = NP ((@) a) ls Source #

The type of multiply-located values.

(~>*) :: forall (l :: Symbol) (ls :: [Symbol]) a (m :: Type -> Type). (KnownSymbol l, All KnownSymbol ls, Show a, Read a) => (Proxy l, a @ l) -> NP (Proxy :: Symbol -> Type) ls -> Choreo m (a @@ ls) infix 4 Source #

"scatter": Send a located value from a single location to many others.

(*~>) :: forall (l :: Symbol) (ls :: [Symbol]) (m :: Type -> Type) a. (KnownSymbol l, All KnownSymbol ls, Applicative m, Show a, Read a) => (a @@ ls) -> Proxy l -> Choreo m (NP (K a :: Symbol -> Type) ls @ l) infix 4 Source #

"gather": Send a multiply-located value from many locations to one.

(~>.) :: forall (l :: Symbol) (ls :: [Symbol]) (m :: Type -> Type) a. (KnownSymbol l, All KnownSymbol ls, Applicative m, Show a, Read a) => (Proxy l, NP (K a :: Symbol -> Type) ls @ l) -> NP (Proxy :: Symbol -> Type) ls -> Choreo m (a @@ ls) infix 4 Source #

Send a list of values from one location to many others "pointwise" (i.e. each target gets one value).

type Unwraps (ls :: [LocTy]) = forall a. (a @@ ls) -> a Source #

Multiply-located version of Unwrap.

type LocalComp (ls :: [LocTy]) (m :: k -> Type) (a :: k) = forall (l :: Symbol). KnownSymbol l => Proxy l -> Unwraps ls -> m a Source #

The type of a (multi)local computation.

multilocally :: forall (ls :: [Symbol]) (m :: Type -> Type) a. All KnownSymbol ls => NP (Proxy :: Symbol -> Type) ls -> LocalComp ls m a -> Choreo m (a @@ ls) Source #

Multiply-located version of locally.

(~~>*) :: forall (l :: Symbol) (ls :: [Symbol]) a m. (KnownSymbol l, All KnownSymbol ls, Show a, Read a) => (Proxy l, Unwrap l -> m a) -> NP (Proxy :: Symbol -> Type) ls -> Choreo m (a @@ ls) infix 4 Source #

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

(*~~>) :: forall (l :: Symbol) (ls :: [Symbol]) (m :: Type -> Type) a. (KnownSymbol l, All KnownSymbol ls, Applicative m, Show a, Read a) => (NP (Proxy :: Symbol -> Type) ls, LocalComp ls m a) -> Proxy l -> Choreo m (NP (K a :: Symbol -> Type) ls @ l) infix 4 Source #

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