Safe Haskell | None |
---|---|
Language | Haskell2010 |
We cannot create a Closure
of a Session
, because its type parameters are of a different kind than *
.
To accomedate for this drawback we define two data types that existentially quantify the type parameters of a Session
.
We also define a set of static and closure functions for remotely spawning sessions.
- data SpawnSession a b where
- SpawnSession :: (HasConstraintST Serializable s, HasConstraintST Serializable (DualST s), Typeable a, Typeable b) => Session (Cap '[] s) r a -> Session (Cap '[] (DualST s)) r b -> SpawnSession a b
- data SessionWrap a where
- SessionWrap :: Session s s a -> SessionWrap a
- sessionRemoteTable :: RemoteTable -> RemoteTable
- remoteSessionStatic :: Static (SerializableDict a -> Closure (SessionWrap a) -> Process a)
- remoteSessionClosure :: Static (SerializableDict a) -> Closure (SessionWrap a) -> Closure (Process a)
- remoteSessionStatic' :: Static (Closure (SessionWrap ()) -> Process ())
- remoteSessionClosure' :: Closure (SessionWrap ()) -> Closure (Process ())
- spawnChannelStatic :: Static (SerializableDict a -> Closure (ReceivePort a -> SessionWrap ()) -> ReceivePort a -> Process ())
- spawnChannelClosure :: Static (SerializableDict a) -> Closure (ReceivePort a -> SessionWrap ()) -> Closure (ReceivePort a -> Process ())
- evalLocalSession :: Typeable a => (ProcessId, NodeId, Closure (SpawnSession a ())) -> Process a
- remoteSpawnSessionStatic :: Static (SerializableDict a -> (ProcessId, NodeId, Closure (SpawnSession a ())) -> Process ())
- remoteSpawnSessionClosure :: Static (SerializableDict a) -> (ProcessId, NodeId, Closure (SpawnSession a ())) -> Closure (Process ())
- remoteSpawnSessionStatic' :: Static ((ProcessId, NodeId, Closure (SpawnSession () ())) -> Process ())
- remoteSpawnSessionClosure' :: (ProcessId, NodeId, Closure (SpawnSession () ())) -> Closure (Process ())
- rrSpawnSessionSendStatic :: Static ((ProcessId, NodeId, Closure (SpawnSession () ())) -> Process ())
- rrSpawnSessionSendClosure :: (ProcessId, NodeId, Closure (SpawnSession () ())) -> Closure (Process ())
- rrSpawnSessionExpectStatic :: Static ((NodeId, Closure (SpawnSession () ())) -> Process ())
- rrSpawnSessionExpectClosure :: (NodeId, Closure (SpawnSession () ())) -> Closure (Process ())
Encapsulation
data SpawnSession a b where Source #
Data type that encapsulates two sessions for the purpose of remotely spawning them
The session types of the sessions are existentially quantified, but we still ensure duality and constrain them properly, such that they can be passed to evalSession
.
SpawnSession :: (HasConstraintST Serializable s, HasConstraintST Serializable (DualST s), Typeable a, Typeable b) => Session (Cap '[] s) r a -> Session (Cap '[] (DualST s)) r b -> SpawnSession a b |
data SessionWrap a where Source #
Data type that encapsulates a single session performing no session typed action that can be remotely spawned.
We use this data type mostly for convenience in combination with evalSessionEq
allowing us to avoid the Serializable
constraint.
SessionWrap :: Session s s a -> SessionWrap a |
RemoteTable
sessionRemoteTable :: RemoteTable -> RemoteTable Source #
RemoteTable that binds all in this module defined static functions to their corresponding evaluation functions.
Static and Closures
Singular
remoteSessionStatic :: Static (SerializableDict a -> Closure (SessionWrap a) -> Process a) Source #
Static function for remotely spawning a single session
When remotely spawning any session we must always pass it the ProcessId
and NodeId
of the spawning process.
We must pass a Closure of a SessionWrap
instead of just a SessionWrap
, because that would require
serializing a SessionWrap
which is not possible.
Furthermore, we must also pass a SerializableDict
that shows how to serialize a value of type a
.
remoteSessionClosure :: Static (SerializableDict a) -> Closure (SessionWrap a) -> Closure (Process a) Source #
Closure function for remotely spawning a single session
remoteSessionStatic' :: Static (Closure (SessionWrap ()) -> Process ()) Source #
Same as remoteSessionStatic
, except that we do not need to provide a SerializableDict
.
remoteSessionClosure' :: Closure (SessionWrap ()) -> Closure (Process ()) Source #
Same as remoteSessionClosure
, except that we do not need to provide a SerializableDict
.
SpawnChannel
spawnChannelStatic :: Static (SerializableDict a -> Closure (ReceivePort a -> SessionWrap ()) -> ReceivePort a -> Process ()) Source #
A static function specific to the lifted spawnChannel
function that can be found in Control.Distributed.Session.Lifted
spawnChannelClosure :: Static (SerializableDict a) -> Closure (ReceivePort a -> SessionWrap ()) -> Closure (ReceivePort a -> Process ()) Source #
A closure specific to the lifted spawnChannel
function that can be found in Control.Distributed.Session.Lifted
Local Remote Evaluation
evalLocalSession :: Typeable a => (ProcessId, NodeId, Closure (SpawnSession a ())) -> Process a Source #
Function that evalutes the first argument of a SpawnSession
in a local manner.
It is local in that we do not create an accompanying closure.
remoteSpawnSessionStatic :: Static (SerializableDict a -> (ProcessId, NodeId, Closure (SpawnSession a ())) -> Process ()) Source #
Static function for remotely evaluating the second argument of a SpawnSession
.
This function works dually to evalLocalSession
.
remoteSpawnSessionClosure :: Static (SerializableDict a) -> (ProcessId, NodeId, Closure (SpawnSession a ())) -> Closure (Process ()) Source #
Closure for remotely evaluating the second argument of a SpawnSession
remoteSpawnSessionStatic' :: Static ((ProcessId, NodeId, Closure (SpawnSession () ())) -> Process ()) Source #
Same as remoteSpawnSessionStatic
, except for that we do not need to provide a SerializableDict
.
remoteSpawnSessionClosure' :: (ProcessId, NodeId, Closure (SpawnSession () ())) -> Closure (Process ()) Source #
Same as remoteSpawnSessionClosure
, except for that we do not need to provide a SerializableDict
.
Remote Remote Evaluation
rrSpawnSessionSendStatic :: Static ((ProcessId, NodeId, Closure (SpawnSession () ())) -> Process ()) Source #
Static function for remotely evaluating the second argument of a SpawnSession
This function is very similar to remoteSpawnSessionStatic'
. The difference is that this function assumes that
the other session was also remotely spawned.
Therefore we require an extra send of the ProcessId
of the to be spawned process.
rrSpawnSessionSendClosure :: (ProcessId, NodeId, Closure (SpawnSession () ())) -> Closure (Process ()) Source #
Closure for remotely evaluating the second argument of a SpawnSession
.
rrSpawnSessionExpectStatic :: Static ((NodeId, Closure (SpawnSession () ())) -> Process ()) Source #
Closure for remotely evaluating the first argument of a SpawnSession
This function acts dual to rrSpawnSessionSend
and assumes that it will first receive a ProcessId
.
rrSpawnSessionExpectClosure :: (NodeId, Closure (SpawnSession () ())) -> Closure (Process ()) Source #
Closure for remotely evaluating the first argument of a SpawnSession
.