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

Safe HaskellNone
LanguageHaskell2010

Control.Distributed.Fork.Backend

Contents

Description

You only need this module if you want to create a new backend for distributed-fork.

See LocalProcessBackend for a minimal example.

Synopsis

Writing a Backend.

newtype Backend Source #

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

See:

Constructors

Backend 

Fields

  • bExecute :: ByteString -> BackendM ByteString

    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.

data BackendM a Source #

BackendM is essentially IO, but also has the ability to report the status of the executor.

Instances

Monad BackendM Source # 

Methods

(>>=) :: BackendM a -> (a -> BackendM b) -> BackendM b #

(>>) :: BackendM a -> BackendM b -> BackendM b #

return :: a -> BackendM a #

fail :: String -> BackendM a #

Functor BackendM Source # 

Methods

fmap :: (a -> b) -> BackendM a -> BackendM b #

(<$) :: a -> BackendM b -> BackendM a #

Applicative BackendM Source # 

Methods

pure :: a -> BackendM a #

(<*>) :: BackendM (a -> b) -> BackendM a -> BackendM b #

liftA2 :: (a -> b -> c) -> BackendM a -> BackendM b -> BackendM c #

(*>) :: BackendM a -> BackendM b -> BackendM b #

(<*) :: BackendM a -> BackendM b -> BackendM a #

MonadIO BackendM Source # 

Methods

liftIO :: IO a -> BackendM a #

MonadThrow BackendM Source # 

Methods

throwM :: Exception e => e -> BackendM a #

MonadCatch BackendM Source # 

Methods

catch :: Exception e => BackendM a -> (e -> BackendM a) -> BackendM a #

argExecutorMode :: String Source #

We switch to executor mode only when argv[1] == argExecutorMode.

Reporting status

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

Re-exports

liftIO :: MonadIO m => forall a. IO a -> m a #

Lift a computation from the IO monad.

getExecutablePath :: IO FilePath #

Returns the absolute pathname of the current executable.

Note that for scripts and interactive sessions, this is the path to the interpreter (e.g. ghci.)

Since: 4.6.0.0