Safe Haskell | None |
---|---|
Language | Haskell98 |
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.
- data SerializableDict a where
- SerializableDict :: Serializable a => SerializableDict a
- staticDecode :: Typeable a => Static (SerializableDict a) -> Static (ByteString -> a)
- sdictUnit :: Static (SerializableDict ())
- sdictProcessId :: Static (SerializableDict ProcessId)
- sdictSendPort :: Typeable a => Static (SerializableDict a) -> Static (SerializableDict (SendPort a))
- type CP a b = Closure (a -> Process b)
- idCP :: Typeable a => CP a a
- splitCP :: (Typeable a, Typeable b, Typeable c, Typeable d) => CP a c -> CP b d -> CP (a, b) (c, d)
- returnCP :: forall a. Serializable a => Static (SerializableDict a) -> a -> Closure (Process a)
- bindCP :: forall a b. (Typeable a, Typeable b) => Closure (Process a) -> CP a b -> Closure (Process b)
- seqCP :: (Typeable a, Typeable b) => Closure (Process a) -> Closure (Process b) -> Closure (Process b)
- cpLink :: ProcessId -> Closure (Process ())
- cpUnlink :: ProcessId -> Closure (Process ())
- cpRelay :: ProcessId -> Closure (Process ())
- cpSend :: forall a. Typeable a => Static (SerializableDict a) -> ProcessId -> CP a ()
- cpExpect :: Typeable a => Static (SerializableDict a) -> Closure (Process a)
- cpNewChan :: Typeable a => Static (SerializableDict a) -> Closure (Process (SendPort a, ReceivePort a))
- type RemoteRegister = RemoteTable -> RemoteTable
- class MkTDict a where
- mkTDict :: String -> a -> RemoteRegister
- mkStaticVal :: Serializable a => String -> a -> (Static a, RemoteRegister)
- mkClosureValSingle :: forall a b. (Serializable a, Typeable b, MkTDict b) => String -> (a -> b) -> (a -> Closure b, RemoteRegister)
- mkClosureVal :: forall func argTuple result closureFunction. (Curry (argTuple -> Closure result) closureFunction, MkTDict result, Uncurry HTrue argTuple func result, Typeable result, Serializable argTuple, IsFunction func HTrue) => String -> func -> (closureFunction, RemoteRegister)
- call' :: forall a. Serializable a => NodeId -> Closure (Process a) -> Process a
- remotable :: [Name] -> Q [Dec]
- remotableDecl :: [Q [Dec]] -> Q [Dec]
- mkStatic :: Name -> Q Exp
- mkClosure :: Name -> Q Exp
- mkStaticClosure :: Name -> Q Exp
- functionSDict :: Name -> Q Exp
- functionTDict :: Name -> Q Exp
Serialization dictionaries (and their static versions)
data SerializableDict a where Source
Reification of Serializable
(see Control.Distributed.Process.Closure)
SerializableDict :: Serializable a => SerializableDict a |
Typeable (* -> *) SerializableDict |
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 '()'
sdictProcessId :: Static (SerializableDict ProcessId) Source
Serialization dictionary for ProcessId
sdictSendPort :: Typeable a => Static (SerializableDict a) -> Static (SerializableDict (SendPort a)) Source
Serialization dictionary for SendPort
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
splitCP :: (Typeable a, Typeable b, Typeable c, Typeable d) => CP a c -> CP b d -> CP (a, b) (c, d) Source
returnCP :: forall a. Serializable a => Static (SerializableDict a) -> a -> Closure (Process a) Source
bindCP :: forall a b. (Typeable a, Typeable b) => Closure (Process a) -> CP a b -> Closure (Process b) Source
seqCP :: (Typeable a, Typeable b) => Closure (Process a) -> Closure (Process b) -> Closure (Process b) Source
CP versions of Cloud Haskell primitives
cpNewChan :: Typeable a => Static (SerializableDict a) -> Closure (Process (SendPort a, ReceivePort a)) Source
Working with static values and closures (without Template Haskell)
type RemoteRegister = RemoteTable -> RemoteTable Source
A RemoteRegister is a trasformer on a RemoteTable to register additional static values.
mkTDict :: String -> a -> RemoteRegister Source
MkTDict a | |
Serializable b => MkTDict (Process b) |
mkStaticVal :: Serializable a => String -> a -> (Static a, RemoteRegister) Source
This takes an explicit name and a value, and produces both a static reference to the name and a RemoteRegister for it.
mkClosureValSingle :: forall a b. (Serializable a, Typeable b, MkTDict b) => String -> (a -> b) -> (a -> Closure b, RemoteRegister) Source
This takes an explicit name, a function of arity one, and creates a creates a function yielding a closure and a remote register for it.
mkClosureVal :: forall func argTuple result closureFunction. (Curry (argTuple -> Closure result) closureFunction, MkTDict result, Uncurry HTrue argTuple func result, Typeable result, Serializable argTuple, IsFunction func HTrue) => String -> func -> (closureFunction, RemoteRegister) Source
This takes an explict name, a function of any arity, and creates a function yielding a closure and a remote register for it.
call' :: forall a. Serializable a => NodeId -> Closure (Process a) -> Process a Source
Works just like standard call, but with a simpler signature.
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
remotableDecl :: [Q [Dec]] -> Q [Dec] Source
Like remotable
, but parameterized by the declaration of a function
instead of the function name. So where for remotable
you'd do
f :: T1 -> T2 f = ... remotable ['f]
with remotableDecl
you would instead do
remotableDecl [ [d| f :: T1 -> T2 ; f = ... |] ]
remotableDecl
creates the function specified as well as the various
dictionaries and static versions that remotable
also creates.
remotableDecl
is sometimes necessary when you want to refer to, say,
$(mkClosure 'f)
within the definition of f
itself.
NOTE: remotableDecl
creates __remoteTableDecl
instead of __remoteTable
so that you can use both remotable
and remotableDecl
within the same
module.
mkStatic :: Name -> Q Exp Source
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 Exp Source
If f : T1 -> T2
then $(mkClosure 'f) :: T1 -> Closure T2
.
TODO: The current version of mkClosure is too polymorphic (@forall a. Binary a => a -> Closure T2).
mkStaticClosure :: Name -> Q Exp Source
Make a Closure
from a static function. This is useful for
making a closure for a top-level Process ()
function, because
using mkClosure
would require adding a dummy ()
argument.