distributed-process-0.3.0: Cloud Haskell: Erlang-style concurrency in Haskell

Safe HaskellNone

Control.Distributed.Process.Closure

Contents

Description

Towards Haskell in the Cloud (Epstein et al., Haskell Symposium 2011) proposes a new type construct called static that characterizes values that are known statically. Cloud Haskell uses the Static implementation from Control.Distributed.Static. That module comes with its own extensive documentation, which you should read if you want to know the details. Here we explain the Template Haskell support only.

Static values

Given a top-level (possibly polymorphic, but unqualified) definition

 f :: forall a1 .. an. T
 f = ...

you can use a Template Haskell splice to create a static version of f:

 $(mkStatic 'f) :: forall a1 .. an. (Typeable a1, .., Typeable an) => Static T

Every module that you write that contains calls to mkStatic needs to have a call to remotable:

 remotable [ 'f, 'g, ... ]

where you must pass every function (or other value) that you pass as an argument to mkStatic. The call to remotable will create a definition

 __remoteTable :: RemoteTable -> RemoteTable

which can be used to construct the RemoteTable used to initialize Cloud Haskell. You should have (at most) one call to remotable per module, and compose all created functions when initializing Cloud Haskell:

 let rtable :: RemoteTable 
     rtable = M1.__remoteTable
            . M2.__remoteTable
            . ...
            . Mn.__remoteTable
            $ initRemoteTable 

NOTE: If you get a type error from ghc along these lines

  The exact Name `a_a30k' is not in scope
       Probable cause: you used a unique name (NameU) in Template Haskell but did not bind it

then you need to enable the ScopedTypeVariables language extension.

Static serialization dictionaries

Some Cloud Haskell primitives require static serialization dictionaries (**):

 call :: Serializable a => Static (SerializableDict a) -> NodeId -> Closure (Process a) -> Process a

Given some serializable type T you can define

 sdictT :: SerializableDict T
 sdictT = SerializableDict

and then have

 $(mkStatic 'sdictT) :: Static (SerializableDict T)

However, since these dictionaries are so frequently required Cloud Haskell provides special support for them. When you call remotable on a monomorphic function f :: T1 -> T2

 remotable ['f]

then a serialization dictionary is automatically created for you, which you can access with

 $(functionSDict 'f) :: Static (SerializableDict T1)

In addition, if f :: T1 -> Process T2, then a second dictionary is created

 $(functionTDict 'f) :: Static (SerializableDict T2)
Closures

Suppose you have a process

 isPrime :: Integer -> Process Bool 

Then

 $(mkClosure 'isPrime) :: Integer -> Closure (Process Bool)

which you can then call, for example, to have a remote node check if a number is prime.

In general, if you have a monomorphic function

 f :: T1 -> T2

then

 $(mkClosure 'f) :: T1 -> Closure T2

provided that T1 is serializable (*) (remember to pass f to remotable).

(You can also create closures manually--see the documentation of Control.Distributed.Static for examples.)

Example

Here is a small self-contained example that uses closures and serialization dictionaries. It makes use of the Control.Distributed.Process.SimpleLocalnet Cloud Haskell backend.

 {-# LANGUAGE TemplateHaskell #-}
 import System.Environment (getArgs)
 import Control.Distributed.Process
 import Control.Distributed.Process.Closure
 import Control.Distributed.Process.Backend.SimpleLocalnet
 import Control.Distributed.Process.Node (initRemoteTable)
 
 isPrime :: Integer -> Process Bool
 isPrime n = return . (n `elem`) . takeWhile (<= n) . sieve $ [2..]
   where
     sieve :: [Integer] -> [Integer]
     sieve (p : xs) = p : sieve [x | x <- xs, x `mod` p > 0]
 
 remotable ['isPrime]
 
 master :: [NodeId] -> Process ()
 master [] = liftIO $ putStrLn "no slaves"
 master (slave:_) = do
   isPrime79 <- call $(functionTDict 'isPrime) slave ($(mkClosure 'isPrime) (79 :: Integer))
   liftIO $ print isPrime79 
 
 main :: IO ()
 main = do
   args <- getArgs
   case args of
     ["master", host, port] -> do
       backend <- initializeBackend host port rtable 
       startMaster backend master 
     ["slave", host, port] -> do
       backend <- initializeBackend host port rtable 
       startSlave backend
   where
     rtable :: RemoteTable
     rtable = __remoteTable initRemoteTable 
Notes

(*) If T1 is not serializable you will get a type error in the generated code. Unfortunately, the Template Haskell infrastructure cannot check a priori if T1 is serializable or not due to a bug in the Template Haskell libraries (http://hackage.haskell.org/trac/ghc/ticket/7066)

(**) Even though call is passed an explicit serialization dictionary, we still need the Serializable constraint because Static is not the true static. If it was, we could unstatic the dictionary and pattern match on it to bring the Typeable instance into scope, but unless proper static support is added to ghc we need both the type class argument and the explicit dictionary.

Synopsis

Template Haskell support for creating static values and closures

remotable :: [Name] -> Q [Dec]Source

Create the closure, decoder, and metadata definitions for the given list of functions

mkStatic :: Name -> Q ExpSource

Construct a static value.

If f : forall a1 .. an. T then $(mkStatic 'f) :: forall a1 .. an. Static T. Be sure to pass f to remotable.

functionSDict :: Name -> Q ExpSource

If f : T1 -> T2 is a monomorphic function then $(functionSDict 'f) :: Static (SerializableDict T1).

Be sure to pass f to remotable.

functionTDict :: Name -> Q ExpSource

If f : T1 -> Process T2 is a monomorphic function then $(functionTDict 'f) :: Static (SerializableDict T2).

Be sure to pass f to remotable.

Serialization dictionaries (and their static versions)

staticDecode :: Typeable a => Static (SerializableDict a) -> Static (ByteString -> a)Source

Static decoder, given a static serialization dictionary.

See module documentation of Control.Distributed.Process.Closure for an example.

sdictUnit :: Static (SerializableDict ())Source

Serialization dictionary for '()'

The CP type and associated combinators

type CP a b = Closure (a -> Process b)Source

CP a b is a process with input of type a and output of type b

idCP :: Typeable a => CP a aSource

CP version of id

splitCP :: (Typeable a, Typeable b, Typeable c, Typeable d) => CP a c -> CP b d -> CP (a, b) (c, d)Source

CP version of (***)

returnCP :: forall a. Serializable a => Static (SerializableDict a) -> a -> Closure (Process a)Source

CP version of return

bindCP :: forall a b. (Typeable a, Typeable b) => Closure (Process a) -> CP a b -> Closure (Process b)Source

(Not quite the) CP version of (>>=)

seqCP :: (Typeable a, Typeable b) => Closure (Process a) -> Closure (Process b) -> Closure (Process b)Source

CP version of (>>)

CP versions of Cloud Haskell primitives

cpSend :: forall a. Typeable a => Static (SerializableDict a) -> ProcessId -> CP a ()Source

CP version of send