Safe Haskell | None |
---|
Control.Distributed.Process.Closure
Contents
Description
Implementation of Closure
that works around the absence of static
.
- Built-in closures
We offer a number of standard commonly useful closures.
- Closure combinators
Closures combinators allow to create closures from other closures. For
example, spawnSupervised
is defined as follows:
spawnSupervised :: NodeId -> Closure (Process ()) -> Process (ProcessId, MonitorRef) spawnSupervised nid proc = do us <- getSelfPid them <- spawn nid (linkClosure us `cpSeq` proc) ref <- monitor them return (them, ref)
- User-defined closures
Suppose we have a monomorphic function
addInt :: Int -> Int -> Int addInt x y = x + y
Then the Template Haskell splice
remotable ['addInt]
creates a function
$(mkClosure 'addInt) :: Int -> Closure (Int -> Int)
which can be used to partially apply addInt
and turn it into a Closure
,
which can be sent across the network. Closures can be deserialized with
unClosure :: Typeable a => Closure a -> Process a
In general, given a monomorphic function f :: a -> b
the corresponding
function $(mkClosure 'f)
will have type a -> Closure b
.
The call to remotable
will also generate a function
__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 = M1.__remoteTable . M2.__remoteTable . ... . Mn.__remoteTable $ initRemoteTable
See Section 6, Faking It, of Towards Haskell in the Cloud for more info.
- Serializable Dictionaries
Some functions (such as sendClosure
or returnClosure
) require an
explicit (reified) serializable dictionary. To create such a dictionary do
serializableDictInt :: SerializableDict Int serializableDictInt = SerializableDict
and then pass 'serializableDictInt
to remotable
. This will fail if the
type is not serializable.
- remotable :: [Name] -> Q [Dec]
- mkClosure :: Name -> Q Exp
- data SerializableDict a where
- SerializableDict :: Serializable a => SerializableDict a
- linkClosure :: ProcessId -> Closure (Process ())
- unlinkClosure :: ProcessId -> Closure (Process ())
- sendClosure :: forall a. SerializableDict a -> ProcessId -> Closure (a -> Process ())
- returnClosure :: forall a. SerializableDict a -> a -> Closure (Process a)
- expectClosure :: forall a. SerializableDict a -> Closure (Process a)
- closureApply :: Closure (a -> b) -> Closure a -> Closure b
- closureConst :: forall a b. (Typeable a, Typeable b) => Closure (a -> b -> a)
- closureUnit :: Closure ()
- type CP a b = Closure (a -> Process b)
- cpIntro :: (Typeable a, Typeable b) => Closure (Process b) -> CP a b
- cpElim :: Typeable a => CP () a -> Closure (Process a)
- cpId :: forall a. Typeable a => CP a a
- cpComp :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP b c -> CP a c
- cpFirst :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (a, c) (b, c)
- cpSwap :: forall a b. (Typeable a, Typeable b) => CP (a, b) (b, a)
- cpSecond :: (Typeable a, Typeable b, Typeable c) => CP a b -> CP (c, a) (c, b)
- cpPair :: (Typeable a, Typeable a', Typeable b, Typeable b') => CP a b -> CP a' b' -> CP (a, a') (b, b')
- cpCopy :: forall a. Typeable a => CP a (a, a)
- cpFanOut :: (Typeable a, Typeable b, Typeable c) => CP a b -> CP a c -> CP a (b, c)
- cpLeft :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (Either a c) (Either b c)
- cpMirror :: forall a b. (Typeable a, Typeable b) => CP (Either a b) (Either b a)
- cpRight :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (Either c a) (Either c b)
- cpEither :: (Typeable a, Typeable a', Typeable b, Typeable b') => CP a b -> CP a' b' -> CP (Either a a') (Either b b')
- cpUntag :: forall a. Typeable a => CP (Either a a) a
- cpFanIn :: (Typeable a, Typeable b, Typeable c) => CP a c -> CP b c -> CP (Either a b) c
- cpApply :: forall a b. (Typeable a, Typeable b) => CP (CP a b, a) b
- cpBind :: (Typeable a, Typeable b) => Closure (Process a) -> Closure (a -> Process b) -> Closure (Process b)
- cpSeq :: Closure (Process ()) -> Closure (Process ()) -> Closure (Process ())
User-defined closures
remotable :: [Name] -> Q [Dec]Source
Create the closure, decoder, and metadata definitions for the given list of functions
mkClosure :: Name -> Q ExpSource
Create a closure
If f :: a -> b
then mkClosure :: a -> Closure b
. Make sure to pass f
as an argument to remotable
too.
data SerializableDict a whereSource
Reification of Serializable
(see Control.Distributed.Process.Closure)
Constructors
SerializableDict :: Serializable a => SerializableDict a |
Instances
Built-in closures
sendClosure :: forall a. SerializableDict a -> ProcessId -> Closure (a -> Process ())Source
Closure version of send
returnClosure :: forall a. SerializableDict a -> a -> Closure (Process a)Source
Return any value
expectClosure :: forall a. SerializableDict a -> Closure (Process a)Source
Closure version of expect
Generic closure combinators
closureApply :: Closure (a -> b) -> Closure a -> Closure bSource
closureConst :: forall a b. (Typeable a, Typeable b) => Closure (a -> b -> a)Source
Arrow combinators for processes
cpPair :: (Typeable a, Typeable a', Typeable b, Typeable b') => CP a b -> CP a' b' -> CP (a, a') (b, b')Source
cpLeft :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (Either a c) (Either b c)Source
cpRight :: forall a b c. (Typeable a, Typeable b, Typeable c) => CP a b -> CP (Either c a) (Either c b)Source
cpEither :: (Typeable a, Typeable a', Typeable b, Typeable b') => CP a b -> CP a' b' -> CP (Either a a') (Either b b')Source