Remote.Call
Description
Provides Template Haskell-based tools and syntactic sugar for dealing with closures
Documentation
remotable :: [Name] -> Q [Dec]Source
A compile-time macro to provide easy invocation of closures. To use this, follow the following steps:
- First, enable Template Haskell in the module:
{-# LANGUAGE TemplateHaskell #-}
module Main where
import Remote.Call (remotable)
...
- Define your functions normally. Restrictions: function's type signature must be explicitly declared; no polymorphism; all parameters must implement Serializable; return value must be pure, or in one of the
ProcessM,TaskM, orIOmonads; probably other restrictions as well.
greet :: String -> ProcessM ()
greet name = say ("Hello, "++name)
badFib :: Integer -> Integer
badFib 0 = 1
badFib 1 = 1
badFib n = badFib (n-1) + badFib (n-2)
- Use the
remotablefunction to automagically generate stubs and closure generators for your functions:
$( remotable ['greet, 'badFib] )
remotable may be used only once per module.
- When you call
remoteInit(usually the first thing in your program), be sure to give it the automagically generated function lookup tables from all modules that useremotable:
main = remoteInit (Just "config") [Main.__remoteCallMetaData, OtherModule.__remoteCallMetaData] initialProcess
- Now you can invoke your functions remotely. When a function expects a closure, give it the name
of the generated closure, rather than the name of the original function. If the function takes parameters,
so will the closure. To start the
greetfunction onsomeNode:
spawn someNode (greet__closure "John Baptist")
Note that we say greet__closure rather than just greet. If you prefer, you can use mkClosure instead, i.e. $(mkClosure 'greet), which will expand to greet__closure. To calculate a Fibonacci number remotely:
val <- callRemotePure someNode (badFib__closure 5)
mkClosure :: Name -> Q ExpSource
A compile-time macro to expand a function name to its corresponding
closure name (if such a closure exists), suitable for use with
spawn, callRemote, etc
In general, using the syntax $(mkClosure foo) is the same
as addressing the closure generator by name, that is,
foo__closure. In some cases you may need to use
mkClosureRec instead.
mkClosureRec :: Name -> Q ExpSource
A variant of mkClosure suitable for expanding closures
of functions declared in the same module, including that
of the function it's used in. The Rec stands for recursive.
If you get the Something is not in scope at a reify message
when using mkClosure, try using this function instead.
Using this function also turns off the static
checks used by mkClosure, and therefore you are responsible
for making sure that you use remotable with each function
that may be an argument of mkClosureRec