Safe Haskell | None |
---|---|
Language | Haskell2010 |
This module provides a common interface for offloading an IO action to remote executors.
It uses StaticPointers language extension and distributed-closure library for serializing closures to run remotely. This blog post is a good introduction for those.
In short, if you you need a
:Closure
a
- If
a
is statically known (eg. a top level value, or if it does not depend on anything on the scope), usestatic
keyword coming fromStaticPointers
extension. - If
a
is a runtime value, usecpure
to lift it toClosure a
. It will ask for a(
. If there isClosure
(Dict
(Serializable
a)))(
andBinary
a)(
instances, you can just useTypeable
a)(static
for that.Dict
)
One important constraint when using this library is that it assumes the remote environment is capable of executing the exact same binary. On most cases, this requires your host environment to be Linux. In future I plan to provide a set of scripts using Docker to overcome this limitation.
- fork :: Backend -> Closure (Dict (Serializable a)) -> Closure (IO a) -> IO (Handle a)
- initDistributedFork :: IO ()
- data Backend
- data Handle a
- await :: Handle a -> IO a
- newtype ExecutorFailedException = ExecutorFailedException Text
- type Serializable a = (Binary a, Typeable * a)
- data Closure a :: * -> *
- cap :: Typeable * a => Closure (a -> b) -> Closure a -> Closure b
- cpure :: Closure (Dict (Serializable a)) -> a -> Closure a
- data Dict a :: Constraint -> * where
Documentation
fork :: Backend -> Closure (Dict (Serializable a)) -> Closure (IO a) -> IO (Handle a) Source #
Asynchronously executes the given function using the Backend
and returns
an Handle
.
{-# LANGUAGE StaticPointers #-} import Control.Distributed.Fork import Control.Distributed.Fork.LocalProcessBackend main :: IO () main = doinitDistributedFork
handle <-fork
localProcessBackend
(staticDict
) (static (return "Hello World!")) await handle >>= putStrLn
initDistributedFork :: IO () Source #
On distributed-fork, we run the same binary both in your machine (called
"driver") and in the remote environment (called "executor"). In order for the
program to act according to where it is, you should call this function as the
first thing in your main
:
main = do initDistributedFork ...
Backend
is responsible for running your functions in a remote environment.
See:
Handle
await :: Handle a -> IO a Source #
Blocks until the Handle
completes.
Can throw ExecutorFailedException
.
Exceptions
newtype ExecutorFailedException Source #
Re-exports
type Serializable a = (Binary a, Typeable * a) #
Values that can be sent across the network.
Type of serializable closures. Abstractly speaking, a closure is a code
reference paired together with an environment. A serializable closure
includes a shareable code reference (i.e. a StaticPtr
). Closures can be
serialized only if all expressions captured in the environment are
serializable.
cap :: Typeable * a => Closure (a -> b) -> Closure a -> Closure b #
Closure application. Note that Closure
is not a functor, let alone an
applicative functor, even if it too has a meaningful notion of application.
cpure :: Closure (Dict (Serializable a)) -> a -> Closure a #
A closure can be created from any serializable value. cpure
corresponds
to Control.Applicative's pure
, but restricted to
lifting serializable values only.
data Dict a :: Constraint -> * where #
Values of type
capture a dictionary for a constraint of type Dict
pp
.
e.g.
Dict
::Dict
(Eq
Int
)
captures a dictionary that proves we have an:
instance Eq
'Int
Pattern matching on the Dict
constructor will bring this instance into scope.
a :=> (Read (Dict a)) | |
a :=> (Monoid (Dict a)) | |
a :=> (Enum (Dict a)) | |
a :=> (Bounded (Dict a)) | |
() :=> (Eq (Dict a)) | |
() :=> (Ord (Dict a)) | |
() :=> (Show (Dict a)) | |
() :=> (Semigroup (Dict a)) | |
a => Bounded (Dict a) | |
a => Enum (Dict a) | |
Eq (Dict a) | |
(Typeable Constraint p, p) => Data (Dict p) | |
Ord (Dict a) | |
a => Read (Dict a) | |
Show (Dict a) | |
Semigroup (Dict a) | |
a => Monoid (Dict a) | |
NFData (Dict c) | |