Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module describes an interpreter for purely evaluating session typed programs
that is based on the paper Beauty in the beast by Swierstra, W., & Altenkirch, T.
Impurity in a session typed programs mainly comes from three things: receives, branching and lifting.
- Using the session type we can easily determine the type of the message that each receive should expect. This information allows us to define a stream of values of different types that provides input for each receive.
- When evaluating a session we send and receive integers to choose a branch in a selection and offering respectively. If we want to purely evaluate a session typed program, then we must provide some kind of input that makes this choice for us.
- The current structure of the
Lift
constructor does not allow us to purely evaluate aLift
. As such a session typed program may not contain a lift for it to be purely evaluated. SeerunM
as an alternative.
- run :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> Output s a
- runAll :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> [a]
- runSingle :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> a
- runP :: HasConstraint Show s => Session s (Cap ctx Eps) a -> SessionInfo -> Stream s -> Process (Output s a)
- runAllP :: HasConstraint Show s => Session s (Cap ctx Eps) a -> SessionInfo -> Stream s -> Process [a]
- runSingleP :: HasConstraint Show s => Session s (Cap ctx Eps) a -> SessionInfo -> Stream s -> Process a
- runM :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> Session r r (Output s a)
- runAllM :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> Session r r [a]
- runSingleM :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> Session r r a
- data Stream a :: Cap Type -> Type where
- S_Send :: Stream (Cap Type ctx ((:!>) Type a1 s))
- S_Recv :: Stream (Cap Type ctx ((:?>) * a1 s))
- S_Sel1 :: Stream (Cap Type ctx (Sel Type ((:) (ST Type) s xs)))
- S_Sel2 :: Stream (Cap Type ctx (Sel Type ((:) (ST Type) s ((:) (ST Type) t xs))))
- S_OffZ :: Stream (Cap Type ctx (Off Type ((:) (ST Type) s ([] (ST Type)))))
- S_OffS :: Stream (Cap Type ctx (Off Type ((:) (ST Type) s ((:) (ST Type) t xs))))
- S_Off1 :: Stream (Cap Type ctx (Off Type ((:) (ST Type) s xs)))
- S_Off2 :: Stream (Cap Type ctx (Off Type ((:) (ST Type) s ((:) (ST Type) t xs))))
- S_Rec :: Stream (Cap Type ctx (R Type s))
- S_Weaken :: Stream (Cap Type ((:) (ST Type) t ctx) (Wk Type s))
- S_Var :: Stream (Cap Type ((:) (ST Type) s ctx) (V Type))
- S_Eps :: Stream (Cap Type ([] (ST Type)) (Eps Type))
- data Output a b :: Cap Type -> Type -> Type where
- O_Send :: Output (Cap Type ctx ((:!>) * a1 r)) b
- O_Recv :: Output (Cap Type ctx ((:?>) * a1 r)) b
- O_Sel1 :: Output (Cap Type ctx (Sel Type ((:) (ST Type) s xs))) b
- O_Sel2 :: Output (Cap Type ctx (Sel Type ((:) (ST Type) s xs))) b
- O_OffZ :: Output (Cap Type ctx (Off Type ((:) (ST Type) s ([] (ST Type))))) b
- O_OffS :: Output (Cap Type ctx (Off Type ((:) (ST Type) s ((:) (ST Type) t xs)))) b
- O_Off1 :: Output (Cap Type ctx (Off Type ((:) (ST Type) s xs))) b
- O_Off2 :: Output (Cap Type ctx (Off Type ((:) (ST Type) s ((:) (ST Type) t xs)))) b
- O_Rec :: Output (Cap Type ctx (R Type s)) b
- O_Var :: Output (Cap Type ((:) (ST Type) s ctx) (V Type)) b
- O_Weaken :: Output (Cap Type ((:) (ST Type) t ctx) (Wk Type s)) b
- O_Eps :: Output (Cap Type ctx (Eps Type)) b
- O_Lift :: Output a b
Pure
run :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> Output s a Source #
Purely evaluates a given Session
using the input defined by Stream
.
The output is described in terms of the session type actions within the given program
An example of how to use this function goes as follows:
prog :: Session ('Cap '[] (Int :!> String :?> Eps)) ('Cap '[] Eps) String prog = send 5 >> recv >>= eps strm = S_Send $ S_Recv "foo" S_Eps
>>>
run prog strm
O_Send 5 $ O_Recv "foo" $ O_Eps "foo"
runAll :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> [a] Source #
Instead of describing the session typed actions, it returns a list of the results of all branches of all offerings.
prog = offer (eps 10) (eps 5) strm = S_OffS S_Eps S_Eps
>>>
runAll prog strm
[10,5]
runP :: HasConstraint Show s => Session s (Cap ctx Eps) a -> SessionInfo -> Stream s -> Process (Output s a) Source #
run
cannot deal with lifted computations. This makes it limited to session typed programs without any use of lift.
This function allows us to evaluate lifted computations, but as a consequence is no longer entirely pure.
runAllP :: HasConstraint Show s => Session s (Cap ctx Eps) a -> SessionInfo -> Stream s -> Process [a] Source #
Monadic version of runAll
.
runSingleP :: HasConstraint Show s => Session s (Cap ctx Eps) a -> SessionInfo -> Stream s -> Process a Source #
Monad version of runSingle
runM :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> Session r r (Output s a) Source #
Session typed version of runP
runAllM :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> Session r r [a] Source #
Session typed version of runAllP
runSingleM :: HasConstraint Show s => Session s (Cap ctx Eps) a -> Stream s -> Session r r a Source #
Session typed version of runSingleP
Input
data Stream a :: Cap Type -> Type where #
We use the Stream
data type to supply input for the receives
in a session typed programs.
We annotate a Stream
with a capability for the following three reasons:
- Each
recv
may return a value of a different type. - Given reason 1 and that we can have branching, we must also be able to branch in the stream.
- We can now write a function that recursively generates input for a recursive program
Similar to STTerm
, Stream
has a constructor for each session type.
Each constructor takes an argument that is another Stream
type, except
for S_Recv
that takes an additional argument that will be used as input, and
S_Eps
that denotes the end of the stream.
At first it might be confusing which constructors and in what order these constructors
should be placed to form a Stream
that can be used as input for some STTerm
.
This is actually not that difficult at all. A Stream
is session typed and that
session type must be equal to the session type of the STTerm
. As such one merely needs to
create a Stream
that has the same session type and if you don't the type checker will tell you
what it incorrect.
There are two things that you need to be aware of when constructor a Stream
.
- The
Stream
constructors for offering (S_OffZ and S_OffS) require that you define input for all branches of the offering. This can be quite cumbersome, so we include aS_Off1
andS_Off2
constructor that behave similarly toS_Sel1
andS_Sel2
. - You are not guaranteed that a
Stream
can be used for all session typed programs that have the same session type. Specifically when it comes to selection can we not guarantee this. The session type for selection only tells us about which branches could be selected. It does not tell us which branch was selected as this is runtime dependent.
S_Send :: Stream (Cap Type ctx ((:!>) Type a1 s)) | |
S_Recv :: Stream (Cap Type ctx ((:?>) * a1 s)) | |
S_Sel1 :: Stream (Cap Type ctx (Sel Type ((:) (ST Type) s xs))) | |
S_Sel2 :: Stream (Cap Type ctx (Sel Type ((:) (ST Type) s ((:) (ST Type) t xs)))) | |
S_OffZ :: Stream (Cap Type ctx (Off Type ((:) (ST Type) s ([] (ST Type))))) | |
S_OffS :: Stream (Cap Type ctx (Off Type ((:) (ST Type) s ((:) (ST Type) t xs)))) | |
S_Off1 :: Stream (Cap Type ctx (Off Type ((:) (ST Type) s xs))) | |
S_Off2 :: Stream (Cap Type ctx (Off Type ((:) (ST Type) s ((:) (ST Type) t xs)))) | |
S_Rec :: Stream (Cap Type ctx (R Type s)) | |
S_Weaken :: Stream (Cap Type ((:) (ST Type) t ctx) (Wk Type s)) | |
S_Var :: Stream (Cap Type ((:) (ST Type) s ctx) (V Type)) | |
S_Eps :: Stream (Cap Type ([] (ST Type)) (Eps Type)) |
HasConstraint Eq s => Eq (Stream s) | |
HasConstraint Show s => Show (Stream s) | |
HasConstraint NFData s => NFData (Stream s) | |
Output
data Output a b :: Cap Type -> Type -> Type where #
The Output
data type describes the session type actions that were done
O_Send :: Output (Cap Type ctx ((:!>) * a1 r)) b | |
O_Recv :: Output (Cap Type ctx ((:?>) * a1 r)) b | |
O_Sel1 :: Output (Cap Type ctx (Sel Type ((:) (ST Type) s xs))) b | |
O_Sel2 :: Output (Cap Type ctx (Sel Type ((:) (ST Type) s xs))) b | |
O_OffZ :: Output (Cap Type ctx (Off Type ((:) (ST Type) s ([] (ST Type))))) b | |
O_OffS :: Output (Cap Type ctx (Off Type ((:) (ST Type) s ((:) (ST Type) t xs)))) b | |
O_Off1 :: Output (Cap Type ctx (Off Type ((:) (ST Type) s xs))) b | |
O_Off2 :: Output (Cap Type ctx (Off Type ((:) (ST Type) s ((:) (ST Type) t xs)))) b | |
O_Rec :: Output (Cap Type ctx (R Type s)) b | |
O_Var :: Output (Cap Type ((:) (ST Type) s ctx) (V Type)) b | |
O_Weaken :: Output (Cap Type ((:) (ST Type) t ctx) (Wk Type s)) b | |
O_Eps :: Output (Cap Type ctx (Eps Type)) b | |
O_Lift :: Output a b |
(HasConstraint Eq s, Eq a) => Eq (Output s a) | |
(HasConstraint Show s, Show a) => Show (Output s a) | |
(HasConstraint NFData s, NFData a) => NFData (Output s a) | |