-- | -- This module provides a common interface for offloading an IO action to remote executors. -- -- It uses -- and -- library -- for serializing closures to run remotely. -- -- 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. module Control.Distributed.Fork ( fork , initDistributedFork , Backend -- * Handle , Handle , await -- * Exceptions , ExecutorFailedException (..) -- * Re-exports , Serializable , Closure , cap , cpure , Dict (Dict) ) where -------------------------------------------------------------------------------- import Control.Distributed.Closure import Control.Monad import Control.Monad.Catch import Data.Text (Text) -------------------------------------------------------------------------------- import Control.Distributed.Fork.Internal -------------------------------------------------------------------------------- -- | -- 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' 'Control.Distributed.Fork.LocalProcessBackend.localProcessBackend' (static 'Dict') (static (return "Hello World!")) -- await handle >>= putStrLn -- @ fork :: Backend -> Closure (Dict (Serializable a)) -> Closure (IO a) -> IO (Handle a) fork b d c = runBackend d c b -- | -- Blocks until the 'Handle' completes. -- -- Can throw 'ExecutorFailedException'. await :: Handle a -> IO a await = tryAwait >=> either (throwM . ExecutorFailedException) return -------------------------------------------------------------------------------- newtype ExecutorFailedException = ExecutorFailedException Text deriving (Show, Eq) instance Exception ExecutorFailedException