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

Safe HaskellNone

Control.Distributed.Process.Closure

Contents

Description

Static values and Closures

Static values

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. There is no support for static in ghc yet, however, so we emulate it using Template Haskell. Given a top-level 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. 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 
Composing static values

We generalize the notion of static as described in the paper, and also provide

 staticApply :: Static (a -> b) -> Static a -> Static b

This makes it possible to define a rich set of combinators on static values, a number of which are provided in this module.

Closures

Suppose you have a process

 factorial :: Int -> Process Int

Then you can use the supplied Template Haskell function mkClosure to define

 factorialClosure :: Int -> Closure (Process Int)
 factorialClosure = $(mkClosure 'factorial)

You can then pass 'factorialClosure n' to spawn, for example, to have a remote node compute a factorial number.

In general, if you have a monomorphic function

 f :: T1 -> T2

then

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

provided that T1 is serializable (*).

Creating closures manually

You don't need to use mkClosure, however. Closures are defined exactly as described in Towards Haskell in the Cloud:

 data Closure a = Closure (Static (ByteString -> a)) ByteString

The splice $(mkClosure 'factorial) above expands to (prettified a bit):

 factorialClosure :: Int -> Closure (Process Int)
 factorialClosure n = Closure decoder (encode n)
   where
     decoder :: Static (ByteString -> Process Int)
     decoder = $(mkStatic 'factorial) 
             `staticCompose`  
               staticDecode $(functionSDict 'factorial)

mkStatic we have already seen:

 $(mkStatic 'factorial) :: Static (Int -> Process Int)

staticCompose is function composition on static functions. staticDecode has type (**)

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

and gives you a static decoder, given a static Serializable dictionary. SerializableDict is a reified type class dictionary, and defined simply as

 data SerializableDict a where
   SerializableDict :: Serializable a => SerializableDict a

That means that for any serialziable type T, you can define

 sdictForMyType :: SerializableDict T
 sdictForMyType = SerializableDict

and then use

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

to obtain a static serializable dictionary for T (make sure to pass sdictForMyType to remotable).

However, since these serialization dictionaries are so frequently required, 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

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

This is the dictionary that mkClosure uses.

Combinators on Closures

Support for staticApply (described above) also means that we can define combinators on Closures, and we provide a number of them in this module, the most important of which is cpBind. Have a look at the implementation of call for an example use.

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 staticDecode is passed an explicit serialization dictionary, we still need the Typeable 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

User-defined 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.

mkClosure :: Name -> Q ExpSource

Create a closure

If f : T1 -> T2 is a monomorphic function then $(mkClosure 'f) :: T1 -> Closure T2. Be sure to pass f to remotable.

functionSDict :: Name -> Q ExpSource

Serialization dictionary for a function argument (see module header)

Primitive operations on static values

staticApply :: Static (a -> b) -> Static a -> Static bSource

Apply two static values

staticDuplicate :: forall a. Typeable a => Static a -> Static (Static a)Source

Co-monadic duplicate for static values

Static functionals

staticConst :: (Typeable a, Typeable b) => Static (a -> b -> a)Source

Static version of const

staticFlip :: (Typeable a, Typeable b, Typeable c) => Static (a -> b -> c) -> Static (b -> a -> c)Source

Static version of flip

staticFst :: (Typeable a, Typeable b) => Static ((a, b) -> a)Source

Static version of fst

staticSnd :: (Typeable a, Typeable b) => Static ((a, b) -> b)Source

Static version of snd

staticCompose :: (Typeable a, Typeable b, Typeable c) => Static (b -> c) -> Static (a -> b) -> Static (a -> c)Source

Static version of (.)

staticFirst :: (Typeable a, Typeable b, Typeable c) => Static ((a -> b) -> (a, c) -> (b, c))Source

Static version of first

staticSecond :: (Typeable a, Typeable b, Typeable c) => Static ((a -> b) -> (c, a) -> (c, b))Source

Static version of second

staticSplit :: (Typeable a, Typeable b, Typeable c, Typeable d) => Static (a -> c) -> Static (b -> d) -> Static ((a, b) -> (c, d))Source

Static version of (***)

Static constants

staticUnit :: Static ()Source

Static version of '()'

Creating closures

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.

staticClosure :: forall a. Typeable a => Static a -> Closure aSource

Convert a static value into a closure.

toClosure :: forall a. Serializable a => Static (SerializableDict a) -> a -> Closure aSource

Convert a serializable value into a closure.

Serialization dictionaries (and their static versions)

sdictUnit :: Static (SerializableDict ())Source

Serialization dictionary for '()'

Definition of CP and the generalized arrow combinators

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

'CP a b' represents the closure of a process parameterized by a and returning b. 'CP a b' forms a (restricted) generalized arrow (http://www.cs.berkeley.edu/~megacz/garrows/)

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

CP introduction form

cpElim :: forall a. Typeable a => CP () a -> Closure (Process a)Source

CP elimination form

cpId :: Typeable a => CP a aSource

Identity (Closure version of return)

cpComp :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP b c -> CP a cSource

Left-to-right composition (Closure version of >=>)

cpFirst :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (a, c) (b, c)Source

First

cpSecond :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (c, a) (c, b)Source

Second

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

Split (Like ***)

cpCancelL :: Typeable a => CP ((), a) aSource

Left cancellation

cpCancelR :: Typeable a => CP (a, ()) aSource

Right cancellation

Closure versions of CH primitives

cpLink :: ProcessId -> Closure (Process ())Source

Closure version of link

cpUnlink :: ProcessId -> Closure (Process ())Source

Closure version of unlink

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

Closure version of send

cpExpect :: Typeable a => Static (SerializableDict a) -> Closure (Process a)Source

Closure version of expect

Closure (Process a) as a not-quite-monad

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

Not-quite-monadic return

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

Not-quite-monadic bind (>>=)

cpSeq :: Closure (Process ()) -> Closure (Process ()) -> Closure (Process ())Source

Monadic sequencing (>>)