module Control.Distributed.Process.Lifted.Extras
( fromProcess
, ProcessProxy
, proxyPid
, spawnProxy
, spawnProxyIO
, inProxy
, fromProxy
)
where
import Control.Exception (SomeException, throw)
import Control.Monad (forever, join, void)
import Control.Monad.Base (MonadBase (..))
import Data.Typeable (Typeable)
import Control.Concurrent.Chan.Lifted (Chan, newChan,
readChan, writeChan)
import Control.Concurrent.MVar.Lifted (newEmptyMVar, putMVar,
takeMVar)
import Control.Distributed.Process.Lifted hiding (newChan)
import Control.Distributed.Process.Node.Lifted (LocalNode,
forkProcess)
fromProcess :: forall a m. (MonadBase IO m)
=> LocalNode -> Process a -> m a
fromProcess node ma =
do resultMV <- newEmptyMVar
void . forkProcess node $
do eresult <- try (do !a <- ma
return a) :: Process (Either SomeException a)
case eresult of
Right result ->
putMVar resultMV result
Left exception ->
putMVar resultMV (throw exception)
!result <- takeMVar resultMV
return result
data ProcessProxy = ProcessProxy {
proxyPid :: !ProcessId,
proxyChan :: !(Chan (Process ()))
} deriving (Typeable)
instance Show ProcessProxy where
show = show . proxyPid
spawnProxy :: Process ProcessProxy
spawnProxy =
do action <- newChan
pid <- spawnLocal . forever $
join (readChan action)
return (ProcessProxy pid action)
spawnProxyIO :: forall m. (MonadBase IO m)
=> LocalNode -> m ProcessProxy
spawnProxyIO node = fromProcess node spawnProxy
inProxy :: forall m. (MonadBase IO m)
=> ProcessProxy -> Process () -> m ()
inProxy = writeChan . proxyChan
fromProxy :: forall a m. (MonadBase IO m)
=> ProcessProxy -> Process a -> m a
fromProxy (ProcessProxy _ prox) ma =
do result <- newEmptyMVar
writeChan prox (ma >>= putMVar result)
takeMVar result