more flexible types for Proto runners
This will allow a runner in the Annex monad.
This commit is contained in:
parent
00f48ac407
commit
94dad1e979
1 changed files with 16 additions and 12 deletions
28
P2P/IO.hs
28
P2P/IO.hs
|
@ -5,7 +5,7 @@
|
||||||
- Licensed under the GNU GPL version 3 or higher.
|
- Licensed under the GNU GPL version 3 or higher.
|
||||||
-}
|
-}
|
||||||
|
|
||||||
{-# LANGUAGE RankNTypes, ScopedTypeVariables, CPP #-}
|
{-# LANGUAGE RankNTypes, ScopedTypeVariables, FlexibleContexts, CPP #-}
|
||||||
|
|
||||||
module P2P.IO
|
module P2P.IO
|
||||||
( RunEnv(..)
|
( RunEnv(..)
|
||||||
|
@ -33,7 +33,7 @@ import qualified Data.ByteString as B
|
||||||
import qualified Data.ByteString.Lazy as L
|
import qualified Data.ByteString.Lazy as L
|
||||||
|
|
||||||
-- Type of interpreters of the Proto free monad.
|
-- Type of interpreters of the Proto free monad.
|
||||||
type RunProto = forall a m. (MonadIO m, MonadMask m) => Proto a -> m (Maybe a)
|
type RunProto m = forall a. (MonadIO m, MonadMask m) => Proto a -> m (Maybe a)
|
||||||
|
|
||||||
data RunEnv = RunEnv
|
data RunEnv = RunEnv
|
||||||
{ runRepo :: Repo
|
{ runRepo :: Repo
|
||||||
|
@ -49,15 +49,13 @@ data RunEnv = RunEnv
|
||||||
runNetProtoHandle :: (MonadIO m, MonadMask m) => RunEnv -> Proto a -> m (Maybe a)
|
runNetProtoHandle :: (MonadIO m, MonadMask m) => RunEnv -> Proto a -> m (Maybe a)
|
||||||
runNetProtoHandle runenv = go
|
runNetProtoHandle runenv = go
|
||||||
where
|
where
|
||||||
go :: RunProto
|
go :: RunProto m
|
||||||
go (Pure v) = pure (Just v)
|
go (Pure v) = pure (Just v)
|
||||||
go (Free (Net n)) = runNetHandle runenv go n
|
go (Free (Net n)) = runNetHandle runenv go n
|
||||||
go (Free (Local _)) = return Nothing
|
go (Free (Local _)) = return Nothing
|
||||||
|
|
||||||
-- Interprater of Net that communicates with a peer over a Handle.
|
-- Interprater of Net that communicates with a peer over a Handle.
|
||||||
--
|
runNetHandle :: (MonadIO m, MonadMask m) => RunEnv -> RunProto m -> NetF (Proto a) -> m (Maybe a)
|
||||||
-- An interpreter for Proto has to be provided.
|
|
||||||
runNetHandle :: (MonadIO m, MonadMask m) => RunEnv -> RunProto -> NetF (Proto a) -> m (Maybe a)
|
|
||||||
runNetHandle runenv runner f = case f of
|
runNetHandle runenv runner f = case f of
|
||||||
SendMessage m next -> do
|
SendMessage m next -> do
|
||||||
v <- liftIO $ tryIO $ do
|
v <- liftIO $ tryIO $ do
|
||||||
|
@ -92,17 +90,23 @@ runNetHandle runenv runner f = case f of
|
||||||
let authed = runCheckAuth runenv t
|
let authed = runCheckAuth runenv t
|
||||||
runner (next authed)
|
runner (next authed)
|
||||||
Relay hin hout next -> do
|
Relay hin hout next -> do
|
||||||
v <- liftIO $ runRelay runner hin hout
|
v <- liftIO $ runRelay runnerio hin hout
|
||||||
case v of
|
case v of
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
Just exitcode -> runner (next exitcode)
|
Just exitcode -> runner (next exitcode)
|
||||||
RelayService service next -> do
|
RelayService service next -> do
|
||||||
v <- liftIO $ runRelayService runenv runner service
|
v <- liftIO $ runRelayService runenv runnerio service
|
||||||
case v of
|
case v of
|
||||||
Nothing -> return Nothing
|
Nothing -> return Nothing
|
||||||
Just () -> runner next
|
Just () -> runner next
|
||||||
|
where
|
||||||
|
-- This is only used for running Net actions when relaying,
|
||||||
|
-- so it's ok to use runNetProtoHandle, despite it not supporting
|
||||||
|
-- all Proto actions.
|
||||||
|
runnerio :: RunProto IO
|
||||||
|
runnerio = runNetProtoHandle runenv
|
||||||
|
|
||||||
runRelay :: RunProto -> RelayHandle -> RelayHandle -> IO (Maybe ExitCode)
|
runRelay :: RunProto IO -> RelayHandle -> RelayHandle -> IO (Maybe ExitCode)
|
||||||
runRelay runner (RelayHandle hout) (RelayHandle hin) = bracket setup cleanup go
|
runRelay runner (RelayHandle hout) (RelayHandle hin) = bracket setup cleanup go
|
||||||
where
|
where
|
||||||
setup = do
|
setup = do
|
||||||
|
@ -117,7 +121,7 @@ runRelay runner (RelayHandle hout) (RelayHandle hin) = bracket setup cleanup go
|
||||||
|
|
||||||
go v = relayHelper runner v hin
|
go v = relayHelper runner v hin
|
||||||
|
|
||||||
runRelayService :: RunEnv -> RunProto -> Service -> IO (Maybe ())
|
runRelayService :: RunEnv -> RunProto IO -> Service -> IO (Maybe ())
|
||||||
runRelayService runenv runner service = bracket setup cleanup go
|
runRelayService runenv runner service = bracket setup cleanup go
|
||||||
where
|
where
|
||||||
cmd = case service of
|
cmd = case service of
|
||||||
|
@ -155,7 +159,7 @@ runRelayService runenv runner service = bracket setup cleanup go
|
||||||
waitexit v pid = putMVar v . RelayDone =<< waitForProcess pid
|
waitexit v pid = putMVar v . RelayDone =<< waitForProcess pid
|
||||||
|
|
||||||
-- Processes RelayData as it is put into the MVar.
|
-- Processes RelayData as it is put into the MVar.
|
||||||
relayHelper :: RunProto -> MVar RelayData -> Handle -> IO (Maybe ExitCode)
|
relayHelper :: RunProto IO -> MVar RelayData -> Handle -> IO (Maybe ExitCode)
|
||||||
relayHelper runner v hin = loop
|
relayHelper runner v hin = loop
|
||||||
where
|
where
|
||||||
loop = do
|
loop = do
|
||||||
|
@ -176,7 +180,7 @@ relayHelper runner v hin = loop
|
||||||
|
|
||||||
-- Takes input from the peer, and puts it into the MVar for processing.
|
-- Takes input from the peer, and puts it into the MVar for processing.
|
||||||
-- Repeats until the peer tells it it's done or hangs up.
|
-- Repeats until the peer tells it it's done or hangs up.
|
||||||
relayFeeder :: RunProto -> MVar RelayData -> IO ()
|
relayFeeder :: RunProto IO -> MVar RelayData -> IO ()
|
||||||
relayFeeder runner v = loop
|
relayFeeder runner v = loop
|
||||||
where
|
where
|
||||||
loop = do
|
loop = do
|
||||||
|
|
Loading…
Add table
Reference in a new issue