distributed-fork-0.0.1.1: Like 'forkIO', but uses remote machines instead of local threads.

Safe HaskellNone
LanguageHaskell2010

Control.Distributed.Fork

Contents

Description

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), use static keyword coming from StaticPointers extension.
  • If a is a runtime value, use cpure to lift it to Closure a. It will ask for a (Closure (Dict (Serializable a))). If there is (Binary a) and (Typeable a) instances, you can just use (static Dict) for that.

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.

Synopsis

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 = do
  initDistributedFork
  handle <- fork localProcessBackend (static Dict) (static (return "Hello World!"))
  putStrLn =<< await handle

await :: Handle a -> IO a Source #

Blocks until the Handle completes.

Can throw ExecutorFailedException.

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

data Backend Source #

Backend is responsible for running your functions in a remote environment.

See:

data Handle a Source #

Result of a fork is an Handle where you can await a result.

data ExecutorFinalStatus a Source #

Instances

Generic (ExecutorFinalStatus a) Source # 

Associated Types

type Rep (ExecutorFinalStatus a) :: * -> * #

Binary a => Binary (ExecutorFinalStatus a) Source # 
type Rep (ExecutorFinalStatus a) Source # 
type Rep (ExecutorFinalStatus a) = D1 * (MetaData "ExecutorFinalStatus" "Control.Distributed.Fork.Internal" "distributed-fork-0.0.1.1-9aGU6IWjuUf565jaocBNN1" False) ((:+:) * (C1 * (MetaCons "ExecutorFailed" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * Text))) (C1 * (MetaCons "ExecutorSucceeded" PrefixI False) (S1 * (MetaSel (Nothing Symbol) NoSourceUnpackedness NoSourceStrictness DecidedLazy) (Rec0 * a))))

Exceptions

Re-exports

type Serializable a = (Binary a, Typeable * a) #

Values that can be sent across the network.

data Closure a :: * -> * #

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.

Instances

IsStatic Closure 

Methods

fromStaticPtr :: StaticPtr a -> Closure a #

Typeable * a => Binary (Closure a) 

Methods

put :: Closure a -> Put #

get :: Get (Closure a) #

putList :: [Closure a] -> Put #

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 Dict p capture a dictionary for a constraint of type p.

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.

Constructors

Dict :: Dict a 

Instances

a :=> (Read (Dict a)) 

Methods

ins :: a :- Read (Dict a) #

a :=> (Monoid (Dict a)) 

Methods

ins :: a :- Monoid (Dict a) #

a :=> (Enum (Dict a)) 

Methods

ins :: a :- Enum (Dict a) #

a :=> (Bounded (Dict a)) 

Methods

ins :: a :- Bounded (Dict a) #

() :=> (Eq (Dict a)) 

Methods

ins :: () :- Eq (Dict a) #

() :=> (Ord (Dict a)) 

Methods

ins :: () :- Ord (Dict a) #

() :=> (Show (Dict a)) 

Methods

ins :: () :- Show (Dict a) #

() :=> (Semigroup (Dict a)) 

Methods

ins :: () :- Semigroup (Dict a) #

a => Bounded (Dict a) 

Methods

minBound :: Dict a #

maxBound :: Dict a #

a => Enum (Dict a) 

Methods

succ :: Dict a -> Dict a #

pred :: Dict a -> Dict a #

toEnum :: Int -> Dict a #

fromEnum :: Dict a -> Int #

enumFrom :: Dict a -> [Dict a] #

enumFromThen :: Dict a -> Dict a -> [Dict a] #

enumFromTo :: Dict a -> Dict a -> [Dict a] #

enumFromThenTo :: Dict a -> Dict a -> Dict a -> [Dict a] #

Eq (Dict a) 

Methods

(==) :: Dict a -> Dict a -> Bool #

(/=) :: Dict a -> Dict a -> Bool #

(Typeable Constraint p, p) => Data (Dict p) 

Methods

gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b) -> (forall g. g -> c g) -> Dict p -> c (Dict p) #

gunfold :: (forall b r. Data b => c (b -> r) -> c r) -> (forall r. r -> c r) -> Constr -> c (Dict p) #

toConstr :: Dict p -> Constr #

dataTypeOf :: Dict p -> DataType #

dataCast1 :: Typeable (* -> *) t => (forall d. Data d => c (t d)) -> Maybe (c (Dict p)) #

dataCast2 :: Typeable (* -> * -> *) t => (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c (Dict p)) #

gmapT :: (forall b. Data b => b -> b) -> Dict p -> Dict p #

gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r #

gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Dict p -> r #

gmapQ :: (forall d. Data d => d -> u) -> Dict p -> [u] #

gmapQi :: Int -> (forall d. Data d => d -> u) -> Dict p -> u #

gmapM :: Monad m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

gmapMp :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

gmapMo :: MonadPlus m => (forall d. Data d => d -> m d) -> Dict p -> m (Dict p) #

Ord (Dict a) 

Methods

compare :: Dict a -> Dict a -> Ordering #

(<) :: Dict a -> Dict a -> Bool #

(<=) :: Dict a -> Dict a -> Bool #

(>) :: Dict a -> Dict a -> Bool #

(>=) :: Dict a -> Dict a -> Bool #

max :: Dict a -> Dict a -> Dict a #

min :: Dict a -> Dict a -> Dict a #

a => Read (Dict a) 
Show (Dict a) 

Methods

showsPrec :: Int -> Dict a -> ShowS #

show :: Dict a -> String #

showList :: [Dict a] -> ShowS #

Semigroup (Dict a) 

Methods

(<>) :: Dict a -> Dict a -> Dict a #

sconcat :: NonEmpty (Dict a) -> Dict a #

stimes :: Integral b => b -> Dict a -> Dict a #

a => Monoid (Dict a) 

Methods

mempty :: Dict a #

mappend :: Dict a -> Dict a -> Dict a #

mconcat :: [Dict a] -> Dict a #

NFData (Dict c) 

Methods

rnf :: Dict c -> () #