distributed-dataset-0.0.1.0: A distributed data processing framework in pure Haskell
Safe HaskellNone
LanguageHaskell2010

Control.Distributed.Fork

Description

This module provides a common interface for offloading an IO action to remote executors.

Synopsis

Documentation

fork :: MonadIO m => Backend -> Closure (Dict (Serializable a)) -> Closure (IO a) -> m (Handle a) Source #

Asynchronously executes the given function using the Backend and returns an Handle.

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:

data Backend Source #

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

Should run the current binary in the target environment, put the given string as standard input and return the executables answer on the standard output. | BackendM is essentially IO, but also has the ability to report the status of the executor.

Handle

data Handle a Source #

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

await :: (MonadIO m, MonadThrow m) => Handle a -> m a Source #

Blocks until the Handle completes.

ExecutorStatus

pollHandle :: Handle a -> STM (ExecutorStatus a) Source #

Get the current status of given Handle.

data ExecutorFinalStatus a Source #

Instances

Instances details
Functor ExecutorFinalStatus Source # 
Instance details

Defined in Control.Distributed.Fork.Internal

Eq a => Eq (ExecutorFinalStatus a) Source # 
Instance details

Defined in Control.Distributed.Fork.Internal

Generic (ExecutorFinalStatus a) Source # 
Instance details

Defined in Control.Distributed.Fork.Internal

Associated Types

type Rep (ExecutorFinalStatus a) :: Type -> Type Source #

Binary a => Binary (ExecutorFinalStatus a) Source # 
Instance details

Defined in Control.Distributed.Fork.Internal

type Rep (ExecutorFinalStatus a) Source # 
Instance details

Defined in Control.Distributed.Fork.Internal

type Rep (ExecutorFinalStatus a) = D1 ('MetaData "ExecutorFinalStatus" "Control.Distributed.Fork.Internal" "distributed-dataset-0.0.1.0-4FGt6FsKf56ZX45G52Nsw" 'False) (C1 ('MetaCons "ExecutorFailed" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 Text)) :+: C1 ('MetaCons "ExecutorSucceeded" 'PrefixI 'False) (S1 ('MetaSel ('Nothing :: Maybe Symbol) 'NoSourceUnpackedness 'NoSourceStrictness 'DecidedLazy) (Rec0 a)))

Exceptions

Re-exports

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

Values that can be sent across the network.

data Closure a Source #

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

Instances details
IsStatic Closure 
Instance details

Defined in Control.Distributed.Closure.Internal

StaticApply Closure 
Instance details

Defined in Control.Applicative.Static

Methods

staticApply :: (Typeable a, Typeable b) => Closure (a -> b) -> Closure a -> Closure b Source #

StaticFunctor Closure 
Instance details

Defined in Data.Functor.Static

Methods

staticMap :: (Typeable a, Typeable b) => Closure (a -> b) -> Closure a -> Closure b Source #

Typeable a => Binary (Closure a) 
Instance details

Defined in Control.Distributed.Closure.Internal

Methods

put :: Closure a -> Put Source #

get :: Get (Closure a) Source #

putList :: [Closure a] -> Put Source #

cap :: Typeable a => Closure (a -> b) -> Closure a -> Closure b Source #

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 Source #

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 where Source #

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 :: forall a. a => Dict a 

Instances

Instances details
HasDict a (Dict a) 
Instance details

Defined in Data.Constraint

Methods

evidence :: Dict a -> Dict a Source #

a :=> (Read (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

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

a :=> (Monoid (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

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

a :=> (Enum (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

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

a :=> (Bounded (Dict a)) 
Instance details

Defined in Data.Constraint

Methods

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

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

Defined in Data.Constraint

Methods

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

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

Defined in Data.Constraint

Methods

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

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

Defined in Data.Constraint

Methods

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

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

Defined in Data.Constraint

Methods

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

a => Bounded (Dict a) 
Instance details

Defined in Data.Constraint

a => Enum (Dict a) 
Instance details

Defined in Data.Constraint

Methods

succ :: Dict a -> Dict a Source #

pred :: Dict a -> Dict a Source #

toEnum :: Int -> Dict a Source #

fromEnum :: Dict a -> Int Source #

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

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

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

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

Eq (Dict a) 
Instance details

Defined in Data.Constraint

Methods

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

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

(Typeable p, p) => Data (Dict p) 
Instance details

Defined in Data.Constraint

Methods

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

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

toConstr :: Dict p -> Constr Source #

dataTypeOf :: Dict p -> DataType Source #

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

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

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

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

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

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

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

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

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

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

Ord (Dict a) 
Instance details

Defined in Data.Constraint

Methods

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

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

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

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

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

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

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

a => Read (Dict a) 
Instance details

Defined in Data.Constraint

Show (Dict a) 
Instance details

Defined in Data.Constraint

Methods

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

show :: Dict a -> String Source #

showList :: [Dict a] -> ShowS Source #

Semigroup (Dict a) 
Instance details

Defined in Data.Constraint

Methods

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

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

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

a => Monoid (Dict a) 
Instance details

Defined in Data.Constraint

Methods

mempty :: Dict a Source #

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

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

NFData (Dict c) 
Instance details

Defined in Data.Constraint

Methods

rnf :: Dict c -> () Source #