Documentation
data OfferImpls whereSource
Use OfferImpls to construct the implementations of the branches
of an offer. Really, it's just a slightly fancy list.
sjump :: forall l prog prog' progOut progIn outgoing incoming. (Dual prog prog', ProgramToMVarsOutgoing prog progOut, ProgramToMVarsOutgoing prog' progIn, SWellFormedConfig l (D0 E) prog, SWellFormedConfig l (D0 E) prog', Elem progOut l (MVar (ProgramCell (Cell outgoing))), Elem progIn l (MVar (ProgramCell (Cell incoming)))) => SessionChain prog progOut progIn (Cons (Jump l) Nil, Cons (Jump l) Nil) (outgoing, incoming) ()Source
Perform a jump. Now you may think that you should indicate where
you want to jump to. But of coures, that's actually specified by
the session type so you don't have to specify it at all in the
implementation.
soffer :: forall finalState finalResult prog prog' progOut progIn jumps. (Dual prog prog', ProgramToMVarsOutgoing prog progOut, ProgramToMVarsOutgoing prog' progIn) => OfferImpls jumps prog progOut progIn finalState finalResult -> SessionChain prog progOut progIn (Cons (Choice jumps) Nil, Cons (Choice jumps) Nil) finalState finalResultSource
Offer a number of branches. This is basically an external choice
- the other party uses sselect
to decide which branch to take.
Use OfferImpls in order to construct the list of implementations of
branches. Note that every implementation must result in the same
final state and emit the same value.
sselect :: forall prog prog' progOut progIn label jumps outgoing incoming len jumpTarget. (Dual prog prog', ProgramToMVarsOutgoing prog progOut, ProgramToMVarsOutgoing prog' progIn, ListLength jumps len, SmallerThan label len, TypeNumberToInt label, Elem jumps label (Cons (Jump jumpTarget) Nil), SWellFormedConfig jumpTarget (D0 E) prog, SWellFormedConfig jumpTarget (D0 E) prog', Elem progOut jumpTarget (MVar (ProgramCell (Cell outgoing))), Elem progIn jumpTarget (MVar (ProgramCell (Cell incoming)))) => label -> SessionChain prog progOut progIn (Cons (Choice jumps) Nil, Cons (Choice jumps) Nil) (outgoing, incoming) ()Source
ssend :: forall t prog prog' progOut progIn nxt incoming. (Dual prog prog', ProgramToMVarsOutgoing prog progOut, ProgramToMVarsOutgoing prog' progIn) => t -> SessionChain prog progOut progIn (Cons t nxt, incoming) (nxt, incoming) ()Source
Send a value to the other party. Of course, the value must be of
the correct type indicated in the session type.
srecv :: forall t prog prog' progOut progIn nxt outgoing. (Dual prog prog', ProgramToMVarsOutgoing prog progOut, ProgramToMVarsOutgoing prog' progIn) => SessionChain prog progOut progIn (outgoing, Cons t nxt) (outgoing, nxt) tSource
Recieve a value from the other party. This will block as
necessary. The type of the value received is specified by the
session type. No magic coercion needed.
run :: (Dual prog prog', ProgramToMVarsOutgoing prog progOut, ProgramToMVarsOutgoing prog' progIn) => prog -> init -> SessionChain prog progOut progIn (Cons (Jump init) Nil, Cons (Jump init) Nil) (toO, toI) res -> SessionChain prog' progIn progOut (Cons (Jump init) Nil, Cons (Jump init) Nil) (toO', toI') res' -> IO (res, res')Source
Run! Provide a program and a start point within that program
(which also then means that all implementations must start with
sjump
), the two implementations which must be duals of each
other, run them, have them communicate, wait until they both finish
and die and then return the results from both of them.
(~>) :: (TyList nxt, SNonTerminal a, SValidSessionType nxt) => a -> nxt -> Cons a nxtSource
data Cons Source
Instances
SListOfJumps (Cons val nxt) => STerminal (Offer (Cons val nxt)) | |
SListOfJumps (Cons val nxt) => STerminal (Select (Cons val nxt)) | |
(ListLength n l, Succ l l', Show n, Show t) => Show (Cons t n) | |
TyList nxt => TyList (Cons val nxt) | |
(SValidSessionType nxt, SNonTerminal val) => SValidSessionType (Cons val nxt) | |
STerminal a => SValidSessionType (Cons a Nil) | |
(SValidSessionType val, SListOfSessionTypes nxt) => SListOfSessionTypes (Cons val nxt) | |
(SListOfJumps nxt, TyNum val) => SListOfJumps (Cons (Cons (Jump val) Nil) nxt) | |
(ListLength n len, Succ len len') => ListLength (Cons t n) len' | |
OnlyOutgoing nxt nxt' => OnlyOutgoing (Cons (Recv t) nxt) nxt' | |
(SNoJumpsBeyond val idx, SNoJumpsBeyond nxt idx) => SNoJumpsBeyond (Cons val nxt) idx | |
(Elem nxt idx' res, Pred idx idx', SmallerThan idx' len, ListLength nxt len) => Elem (Cons val nxt) idx res | |
Elem (Cons res nxt) (D0 E) res | |
OnlyOutgoing (Cons (Offer jl) Nil) (Cons (Choice jl) Nil) | |
OnlyOutgoing (Cons (Select jl) Nil) (Cons (Choice jl) Nil) | |
OnlyOutgoing (Cons (Jump l) Nil) (Cons (Jump l) Nil) | |
OnlyOutgoing nxt nxt' => OnlyOutgoing (Cons (Send t) nxt) (Cons t nxt') | |
OnlyOutgoing (Cons End Nil) (Cons End Nil) | |
(Dual val val', Dual nxt nxt') => Dual (Cons val nxt) (Cons val' nxt') | |
(ProgramToMVarsOutgoing nxt nxt', OnlyOutgoing val val') => ProgramToMVarsOutgoing (Cons val nxt) (Cons (MVar (ProgramCell (Cell val'))) nxt') | |
data D0 n Source
Instances
ListLength Nil (D0 E) | |
Pred m m' => Add m (D0 E) m | |
Show n => Show (D0 n) | |
TypeNumberToInt (D0 E) | |
TyNum n => TyNum (D0 n) | |
TyNum (D0 E) | |
Pred y y' => SmallerThan (D0 E) y | |
StripLeadingZeros a b => StripLeadingZeros (D0 a) b | |
Pred n n' => Add (D0 E) n n | |
Reverse' n (D0 a) r => Reverse' (D0 n) a r | |
StripLeadingZeros (D0 E) (D0 E) | |
DecrementRightToLeft (D1 a) (D0 a) | |
DecrementRightToLeft a b => DecrementRightToLeft (D0 a) (D9 b) | |
IncrementRightToLeft a b => IncrementRightToLeft (D9 a) (D0 b) | |
IncrementRightToLeft (D0 a) (D1 a) | |
Add (D0 E) (D0 E) (D0 E) | |
Elem (Cons res nxt) (D0 E) res | |
data D1 n Source
Instances
IncrementRightToLeft E (D1 E) | |
Show n => Show (D1 n) | |
TyNum n => TyNum (D1 n) | |
TyNum (D1 E) | |
Reverse' n (D1 a) r => Reverse' (D1 n) a r | |
StripLeadingZeros (D1 a) (D1 a) | |
DecrementRightToLeft (D2 a) (D1 a) | |
DecrementRightToLeft (D1 a) (D0 a) | |
IncrementRightToLeft (D1 a) (D2 a) | |
IncrementRightToLeft (D0 a) (D1 a) | |
data D2 n Source
Instances
Show n => Show (D2 n) | |
TyNum n => TyNum (D2 n) | |
TyNum (D2 E) | |
Reverse' n (D2 a) r => Reverse' (D2 n) a r | |
StripLeadingZeros (D2 a) (D2 a) | |
DecrementRightToLeft (D3 a) (D2 a) | |
DecrementRightToLeft (D2 a) (D1 a) | |
IncrementRightToLeft (D2 a) (D3 a) | |
IncrementRightToLeft (D1 a) (D2 a) | |
data D3 n Source
Instances
Show n => Show (D3 n) | |
TyNum n => TyNum (D3 n) | |
TyNum (D3 E) | |
Reverse' n (D3 a) r => Reverse' (D3 n) a r | |
StripLeadingZeros (D3 a) (D3 a) | |
DecrementRightToLeft (D4 a) (D3 a) | |
DecrementRightToLeft (D3 a) (D2 a) | |
IncrementRightToLeft (D3 a) (D4 a) | |
IncrementRightToLeft (D2 a) (D3 a) | |
data D4 n Source
Instances
Show n => Show (D4 n) | |
TyNum n => TyNum (D4 n) | |
TyNum (D4 E) | |
Reverse' n (D4 a) r => Reverse' (D4 n) a r | |
StripLeadingZeros (D4 a) (D4 a) | |
DecrementRightToLeft (D5 a) (D4 a) | |
DecrementRightToLeft (D4 a) (D3 a) | |
IncrementRightToLeft (D4 a) (D5 a) | |
IncrementRightToLeft (D3 a) (D4 a) | |
data D5 n Source
Instances
Show n => Show (D5 n) | |
TyNum n => TyNum (D5 n) | |
TyNum (D5 E) | |
Reverse' n (D5 a) r => Reverse' (D5 n) a r | |
StripLeadingZeros (D5 a) (D5 a) | |
DecrementRightToLeft (D6 a) (D5 a) | |
DecrementRightToLeft (D5 a) (D4 a) | |
IncrementRightToLeft (D5 a) (D6 a) | |
IncrementRightToLeft (D4 a) (D5 a) | |
data D6 n Source
Instances
Show n => Show (D6 n) | |
TyNum n => TyNum (D6 n) | |
TyNum (D6 E) | |
Reverse' n (D6 a) r => Reverse' (D6 n) a r | |
StripLeadingZeros (D6 a) (D6 a) | |
DecrementRightToLeft (D7 a) (D6 a) | |
DecrementRightToLeft (D6 a) (D5 a) | |
IncrementRightToLeft (D6 a) (D7 a) | |
IncrementRightToLeft (D5 a) (D6 a) | |
data D7 n Source
Instances
Show n => Show (D7 n) | |
TyNum n => TyNum (D7 n) | |
TyNum (D7 E) | |
Reverse' n (D7 a) r => Reverse' (D7 n) a r | |
StripLeadingZeros (D7 a) (D7 a) | |
DecrementRightToLeft (D8 a) (D7 a) | |
DecrementRightToLeft (D7 a) (D6 a) | |
IncrementRightToLeft (D7 a) (D8 a) | |
IncrementRightToLeft (D6 a) (D7 a) | |
data D8 n Source
Instances
Show n => Show (D8 n) | |
TyNum n => TyNum (D8 n) | |
TyNum (D8 E) | |
Reverse' n (D8 a) r => Reverse' (D8 n) a r | |
StripLeadingZeros (D8 a) (D8 a) | |
DecrementRightToLeft (D9 a) (D8 a) | |
DecrementRightToLeft (D8 a) (D7 a) | |
IncrementRightToLeft (D8 a) (D9 a) | |
IncrementRightToLeft (D7 a) (D8 a) | |
data D9 n Source
Instances
Show n => Show (D9 n) | |
TyNum n => TyNum (D9 n) | |
TyNum (D9 E) | |
Reverse' n (D9 a) r => Reverse' (D9 n) a r | |
StripLeadingZeros (D9 a) (D9 a) | |
DecrementRightToLeft (D9 a) (D8 a) | |
DecrementRightToLeft a b => DecrementRightToLeft (D0 a) (D9 b) | |
IncrementRightToLeft a b => IncrementRightToLeft (D9 a) (D0 b) | |
IncrementRightToLeft (D8 a) (D9 a) | |
class SMonad m whereSource
An extension of the typical Monad such that you track additional
from
and to
parameters. Thus you can think of this like State
where the type of the State
varies.