sessiontypes-distributed-0.1.0: Package for annotating Cloud Haskell programs

Safe HaskellNone
LanguageHaskell2010

Control.Distributed.Session.Lifted

Description

In this module we lift all functions in Control.Distributed.Process that return a function of type Process a to Session s s a.

Since the functions in this module work identical to the ones in Control.Distributed.Process we will refer to that module for documentation.

There is however some explanation required for functions that take a Process as an argument.

For the functions that also take a Process a as an argument we derive two functions. One that still takes a Process a and one that takes a Session s s a.

There are also functions that take a Closure (Process ()) as an argument. We cannot lift this to be Closure (Session s s ()) as is explained in Control.Distributed.Session.Closure.

To accomodate for this drawback we instead have these functions take a Closure (SessionWrap ()) as an argument.

Here is an example on how to call call.

{-# LANGUAGE TemplateHaskell #-}
import qualified SessionTypes.Indexed as I
import Control.Distributed.Session (SessionWrap(..), sessionRemoteTable, call, evalSessionEq)
import Control.Distributed.Process (liftIO, Process, RemoteTable, NodeId)
import Control.Distributed.Process.Serializable (SerializableDict(..))
import Control.Distributed.Process.Closure (remotable, mkStaticClosure, mkStatic)
import Control.Distributed.Process.Node
import Network.Transport.TCP

sessWrap :: SessionWrap Int
sessWrap = SessionWrap $ I.return 5

sdictInt :: SerializableDict Int
sdictInt = SerializableDict

remotable ['sdictInt, 'sessWrap]

p1 :: NodeId -> Process ()
p1 nid = do
  a <- evalSessionEq (call $(mkStatic 'sdictInt) nid $(mkStaticClosure 'sessWrap))
  liftIO $ putStrLn $ show a

myRemoteTable :: RemoteTable
myRemoteTable = Main.__remoteTable $ sessionRemoteTable initRemoteTable

main :: IO ()
main = do
  Right t <- createTransport "127.0.0.1" "100000" defaultTCPParameters
  node <- newLocalNode t myRemoteTable
  runProcess node $ p1 (localNodeId node)

>>> main
> 5

In p1 we run a session that makes a call and then prints out the result of that call.

Note that this is the call function from SessionTyped.Distributed.Process.Lifted. It takes a Static (SerializableDict a) and a Closure (SessionWrap a).

To create a static serializable dictionary we first have to define a function that returns a monomorphic serializable dictionary.

sdictInt :: SerializableDict Int
sdictInt = SerializableDict

We then pass 'sdictInt to remoteable, which is a top-level Template Haskell splice.

remoteable ['sdictInt]

Now we can create a static serializable dictionary with

$(mkStatic 'sdictInt)

To create a closure for a Session s s we have to wrap it in a SessionWrap.

sessWrap :: SessionWrap Int
sessWrap = SessionWrap $ I.return 5

Similarly to sdictInt this needs to be a top level definition such that we can use Template Haskell to derive a Closure

remotable ['sdictInt, 'sessWrap]
$(mkStaticClosure 'sessWrap)

Since call makes use of internally defined closures, you also have to include sessionRemoteTable.

myRemoteTable = Main.__remoteTable $ sessionRemoteTable initRemoteTable

The remote tables contains a mapping from labels to evaluation functions that a node uses to evaluate closures.

node <- newLocalNode t myRemoteTable

Synopsis

Documentation

utsend :: Serializable a => ProcessId -> a -> Session s s () Source #

Unsession typed send

usend :: Serializable a => ProcessId -> a -> Session s s () Source #

Unsafe send

sendChan :: Serializable a => SendPort a -> a -> Session s s () Source #

receiveWait :: [Match b] -> Session s s b Source #

handleMessage :: Serializable a => Message -> (a -> Session s s b) -> Session r r (Maybe b) Source #

handleMessage_ :: Serializable a => Message -> (a -> Session s s ()) -> Session r r () Source #

handleMessageP_ :: Serializable a => Message -> (a -> Process ()) -> Session s s () Source #

handleMessageIf :: Serializable a => Message -> (a -> Bool) -> (a -> Session s s b) -> Session r r (Maybe b) Source #

handleMessageIf_ :: Serializable a => Message -> (a -> Bool) -> (a -> Session s s ()) -> Session r r () Source #

handleMessageIfP :: Serializable a => Message -> (a -> Bool) -> (a -> Process b) -> Session s s (Maybe b) Source #

handleMessageIfP_ :: Serializable a => Message -> (a -> Bool) -> (a -> Process ()) -> Session s s () Source #

proxy :: Serializable a => ProcessId -> (a -> Session s s Bool) -> Session r r () Source #

proxyP :: Serializable a => ProcessId -> (a -> Process Bool) -> Session s s () Source #

die :: Serializable a => a -> Session s s b Source #

exit :: Serializable a => ProcessId -> a -> Session s s () Source #

catchExit :: (Show a, Serializable a) => Session s s b -> (ProcessId -> a -> Session r r b) -> Session t t b Source #

catchExitP :: (Show a, Serializable a) => Process b -> (ProcessId -> a -> Process b) -> Session s s b Source #

catchesExit :: Session s s b -> [ProcessId -> Message -> Session r r (Maybe b)] -> Session t t b Source #

unStatic :: Typeable a => Static a -> Session s s a Source #

say :: String -> Session s s () Source #

nsend :: Serializable a => String -> a -> Session s s () Source #

callLocal :: Session s s a -> Session s s a Source #