{-# LANGUAGE CPP #-} {-# LANGUAGE GADTs #-} module Connection.Tox where import qualified Connection as G ;import Connection (Manager (..), Policy (..)) import Control.Concurrent.STM import Control.Monad import Data.Dependent.Sum import Data.Functor.Identity import qualified Data.Map as Map import Connection.Tox.Threads import Network.Tox.NodeId import PingMachine import Text.Read #ifdef THREAD_DEBUG import Control.Concurrent.Lifted.Instrument #else import Control.Concurrent.Lifted import GHC.Conc (labelThread) #endif data Parameters = Parameters { -- | Various Tox transports and clients. -- toxTransports :: Tox -- | Thread to be forked when a connection is established. -- TODO: this function should accept relevant parameters. onToxSession :: IO () } data Key = Key NodeId{-me-} NodeId{-them-} deriving (Eq,Ord) instance Show Key where show = show . showKey_ -- | A conneciton status that is tagged with a state type that is specific to -- the status. data Transient a where IsDormant :: Transient () IsAwaitingDHTKey :: Transient () IsAcquiringIPAddress :: Transient () IsAcquiringCookie :: Transient () IsAwaitingHandshake :: Transient () IsAwaitingSessionPacket :: Transient () IsEstablished :: Transient () untag :: DSum Transient Identity -> G.Status ToxProgress untag (IsDormant :=> _) = G.Dormant untag (IsAwaitingDHTKey :=> _) = G.InProgress AwaitingDHTKey untag (IsAcquiringIPAddress :=> _) = G.InProgress AcquiringIPAddress untag (IsAcquiringCookie :=> _) = G.InProgress AcquiringCookie untag (IsAwaitingHandshake :=> _) = G.InProgress AwaitingHandshake untag (IsAwaitingSessionPacket :=> _) = G.InProgress AwaitingSessionPacket untag (IsEstablished :=> _) = G.Established data SessionState = SessionState { transient :: TVar (DSum Transient Identity) , connPolicy :: TVar Policy , connPingLogic :: PingMachine } sessionStatus :: SessionState -> G.Connection ToxProgress sessionStatus st = G.Connection { G.connStatus = untag <$> readTVar (transient st) , G.connPolicy = readTVar (connPolicy st) , G.connPingLogic = connPingLogic st } lookupForPolicyChange :: TVar (Map.Map Key SessionState) -> Key -> Policy -> IO (Maybe SessionState) lookupForPolicyChange conmap k policy = atomically $ do cons <- readTVar conmap fmap join $ forM (Map.lookup k cons) $ \st -> do p <- readTVar (connPolicy st) writeTVar (connPolicy st) policy return $ do guard $ p /= policy return st -- | This function will fork threads as necessary. setToxPolicy :: Parameters -> TVar (Map.Map Key SessionState) -> Key -> Policy -> IO () setToxPolicy params conmap k policy = case policy of TryingToConnect -> do mst <- lookupForPolicyChange conmap k policy forM_ mst $ \st -> do let getPolicy = readTVar $ connPolicy st --TODO accept_thread may already be started if policy was OpenToConnect accept_thread <- forkIO $ acceptContact getPolicy _accept_methods persue_thread <- forkIO $ persueContact getPolicy _get_status _persue_methods freshen_thread <- forkIO $ freshenContact getPolicy _get_status _freshen_methods return () return () RefusingToConnect -> do -- disconnect or cancel any pending connection mst <- lookupForPolicyChange conmap k policy -- Since the 3 connection threads poll the current policy, they should -- all terminate on their own. return () OpenToConnect -> do -- passively accept connections if they initiate. mst <- lookupForPolicyChange conmap k policy forM_ mst $ \st -> do let getPolicy = readTVar $ connPolicy st accept_thread <- forkIO $ acceptContact getPolicy _accept_methods return () showKey_ :: Key -> String showKey_ (Key me them) = show me ++ ":" ++ show them stringToKey_ :: String -> Maybe Key stringToKey_ s = let (xs,ys) = break (==':') s in if null ys then Nothing else do me <- readMaybe xs them <- readMaybe (drop 1 ys) return $ Key me them toxManager :: Parameters -> IO (Manager ToxProgress Key) toxManager params = do conmap <- newTVarIO Map.empty return Manager { setPolicy = setToxPolicy params conmap -- k -> Policy -> IO () , connections = fmap sessionStatus <$> readTVar conmap -- STM (Map k (Connection status)) , stringToKey = stringToKey_ -- String -> Maybe k , showProgress = show -- status -> String , showKey = showKey_ -- k -> String }