MultiChor-1.1.0.0: Type-safe and efficient choreographies with location-set polymorphism.
Safe HaskellSafe-Inferred
LanguageGHC2021

Choreography.Locations

Description

This module defines locations (AKA parties) and functions/relations pertaining to type-level lists of locations.

Synopsis

Type aliases

type LocTm = String Source #

Term-level locations.

type LocTy = Symbol Source #

Type-level locations.

Membership and Subset proofs

data Member (x :: k) (xs :: [k]) where Source #

A term-level proof that a LocTy is a member of a [LocTy]. These are frequently used both for proofs per se and to identify individuals in lists of locations.

For example: player :: Member players census is a proof that the type-level Symbol, player, is in census, and it can also be used as a term-level identifier for the type-level player, similar to how a proxy might be used.

Pattern matching on these values is like pattern matching on a successor-based Nat; in this sense a Member x xs is an index into xs at which x can be found.

Constructors

First :: forall xs x xs'. xs ~ (x ': xs') => Member x (x ': xs') 
Later :: Member x xs -> Member x (y ': xs) 

Instances

Instances details
(KnownSymbol l, ExplicitMember l ls) => CanSend (Member l ps, Located ls a) l a ls ps Source # 
Instance details

Defined in Choreography.Choreography

Methods

presentToSend :: (Member l ps, Located ls a) -> Member l ps Source #

ownsMessagePayload :: (Member l ps, Located ls a) -> Member l ls Source #

structMessagePayload :: (Member l ps, Located ls a) -> Located ls a Source #

KnownSymbol l => CanSend (Member l ps, (Member l ls, Located ls a)) l a ls ps Source # 
Instance details

Defined in Choreography.Choreography

Methods

presentToSend :: (Member l ps, (Member l ls, Located ls a)) -> Member l ps Source #

ownsMessagePayload :: (Member l ps, (Member l ls, Located ls a)) -> Member l ls Source #

structMessagePayload :: (Member l ps, (Member l ls, Located ls a)) -> Located ls a Source #

KnownSymbol l => CanSend (Member l ls, Subset ls ps, Located ls a) l a ls ps Source # 
Instance details

Defined in Choreography.Choreography

Methods

presentToSend :: (Member l ls, Subset ls ps, Located ls a) -> Member l ps Source #

ownsMessagePayload :: (Member l ls, Subset ls ps, Located ls a) -> Member l ls Source #

structMessagePayload :: (Member l ls, Subset ls ps, Located ls a) -> Located ls a Source #

newtype Subset xs ys Source #

A term level proof that one type-level list represents a subset of another, embodied by a total function from proof-of-membership in the sublist to proof-of-membership in the superlist. (If you make one with a partial funciton, all bets are off.)

Constructors

Subset 

Fields

  • inSuper :: forall x. Member x xs -> Member x ys

    Convert a proof of membership in the sublist to a proof of membership in the superlist. Frequently used to show that a location is part of a larger set of locations.

Instances

Instances details
KnownSymbol l => CanSend (Member l ls, Subset ls ps, Located ls a) l a ls ps Source # 
Instance details

Defined in Choreography.Choreography

Methods

presentToSend :: (Member l ls, Subset ls ps, Located ls a) -> Member l ps Source #

ownsMessagePayload :: (Member l ls, Subset ls ps, Located ls a) -> Member l ls Source #

structMessagePayload :: (Member l ls, Subset ls ps, Located ls a) -> Located ls a Source #

refl :: Subset xs xs Source #

The subset relation is reflexive.

transitive :: Subset xs ys -> Subset ys zs -> Subset xs zs Source #

The sublist relation is transitive.

nobody :: Subset '[] ys Source #

The `[]` case of subset proofs. Typlically used to build subset proofs using membership proofs using @@.

consSet :: forall xs x xs'. xs ~ (x ': xs') => Subset xs' (x ': xs') Source #

Any lists is a subset of the list made by consing itself with any other item.

consSuper :: forall xs ys y. Subset xs ys -> Subset xs (y ': ys) Source #

Cons an element to the superset in a Subset value.

(@@) :: Member x ys -> Subset xs ys -> Subset (x ': xs) ys infixr 5 Source #

Cons an element to the subset in a Subset value; requires proof that the new head element is already a member of the superset. Used like ":" for subset proofs. Suppose you have (alice :: Member Alice census) and we want a subset proof instead of membership; we can write:

>>> proof :: Subset '["Alice"] census = alice @@ nobody

Accessing parties' names

toLocTm :: forall (l :: LocTy) (ps :: [LocTy]). KnownSymbol l => Member l ps -> LocTm Source #

Convert a proof-level location to a term-level location.

toLocs :: forall (ls :: [LocTy]) (ps :: [LocTy]). KnownSymbols ls => Subset ls ps -> [LocTm] Source #

Get the term-level list of names-as-strings for a proof-level list of parties.

Handling type-level lists literals

KnownSymbols constraints will often need to be declared in user code, but using tySpine should only be necessary when the behavior of the choreography depends on the structure of the type-level lists. Most of the time the functions in Choreography.Polymorphism should do this for you.

data TySpine ps where Source #

Term-level markers of the spine/structure of a type-level list. Pattern matching on them recovers both the spine of the list and, if applicable, KnownSymbol[s] instances for the head and tail.

Constructors

TyCons :: (KnownSymbol h, KnownSymbols ts) => TySpine (h ': ts)

Denotes that the list has a head and tail, and exposes KnownSymbol and KnownSymbols constraints respectively.

TyNil :: TySpine '[]

Denotes that the list is empty.

class KnownSymbols ls where Source #

The type-level-list version of KnownSymbol. Denotes that both the spine of the list and each of its elements is known at compile-time. This knowlege is typically recovered by recursively pattern-matching on tySpine @ls.

Methods

tySpine :: TySpine ls Source #

Pattern matching on tySpine @ls will normally have two cases, for when ls is empty or not. Contextual knowledge may let one or the other case be skipped. Within those cases, the knowledge afforded by tySpine's constructors can be used.

Instances

Instances details
KnownSymbols ('[] :: [Symbol]) Source # 
Instance details

Defined in Choreography.Locations

Methods

tySpine :: TySpine '[] Source #

(KnownSymbols ls, KnownSymbol l) => KnownSymbols (l ': ls) Source # 
Instance details

Defined in Choreography.Locations

Methods

tySpine :: TySpine (l ': ls) Source #