summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2018-06-13 14:51:04 -0400
committerjoe <joe@jerkface.net>2018-06-13 15:07:53 -0400
commitfd3f604f8961d7c7db48015c9ed7be40ea872a7c (patch)
treee53960ea57a8838ae3e3a63df07aaaf3aeef1f65
parent7cdb8da4f1c6df5d4b2755498e79c9886fd0750f (diff)
tox: WIP connection manager for tox sessions.
-rw-r--r--Connection/Tox.hs112
-rw-r--r--Connection/Tox/Threads.hs66
2 files changed, 104 insertions, 74 deletions
diff --git a/Connection/Tox.hs b/Connection/Tox.hs
index 1d133628..c8ce9a53 100644
--- a/Connection/Tox.hs
+++ b/Connection/Tox.hs
@@ -1,82 +1,26 @@
1{-# LANGUAGE CPP #-}
1{-# LANGUAGE GADTs #-} 2{-# LANGUAGE GADTs #-}
2module Connection.Tox where 3module Connection.Tox where
3 4
4import qualified Connection as G 5import qualified Connection as G
5 ;import Connection (Manager (..), Policy (..)) 6 ;import Connection (Manager (..), Policy (..))
6import Control.Concurrent.STM 7import Control.Concurrent.STM
7-- import Crypto.Tox 8import Control.Monad
8import Data.Dependent.Sum 9import Data.Dependent.Sum
9import Data.Functor.Identity 10import Data.Functor.Identity
10import qualified Data.Map as Map 11import qualified Data.Map as Map
11-- import Data.Maybe 12import Connection.Tox.Threads
12-- import Network.Tox
13import Network.Tox.NodeId 13import Network.Tox.NodeId
14import PingMachine 14import PingMachine
15import Text.Read 15import Text.Read
16#ifdef THREAD_DEBUG
17import Control.Concurrent.Lifted.Instrument
18#else
19import Control.Concurrent.Lifted
20import GHC.Conc (labelThread)
21#endif
16 22
17 23
18-- | This type indicates the progress of a tox encrypted friend link
19-- connection. Two scenarios are illustrated below. The parenthesis show the
20-- current 'G.Status' 'ToxProgress' of the session.
21--
22--
23-- Perfect handshake scenario:
24--
25-- Peer 1 Peer 2
26-- (InProgress AcquiringCookie) (Dormant/InProgress AcquiringCookie)
27-- Cookie request ->
28-- <- Cookie response
29-- (InProgress AwaitingHandshake) (Dormant/InProgress AcquiringCookie)
30-- Handshake packet ->
31-- * accepts connection
32-- (InProgress AwaitingSessionPacket)
33-- <- Handshake packet
34-- *accepts connection
35-- (InProgress AwaitingSessionPacket)
36-- Encrypted packet -> <- Encrypted packet
37-- *confirms connection *confirms connection
38-- (Established) (Established)
39--
40-- Connection successful.
41--
42-- Encrypted packets -> <- Encrypted packets
43--
44--
45--
46--
47-- More realistic handshake scenario:
48-- Peer 1 Peer 2
49-- (InProgress AcquiringCookie) (Dormant/InProgress AcquiringCookie)
50-- Cookie request -> *packet lost*
51-- Cookie request ->
52-- <- Cookie response
53-- (InProgress AwaitingHandshake) (Dormant/InProgress AcquiringCookie)
54--
55-- *Peer 2 randomly starts new connection to peer 1
56-- (InProgress AcquiringCookie)
57-- <- Cookie request
58-- Cookie response ->
59-- (InProgress AwaitingHandshake)
60--
61-- Handshake packet -> <- Handshake packet
62-- *accepts connection * accepts connection
63-- (InProgress AwaitingSessionPacket) (InProgress AwaitingSessionPacket)
64--
65-- Encrypted packet -> <- Encrypted packet
66-- *confirms connection *confirms connection
67-- (Established) (Established)
68--
69-- Connection successful.
70--
71-- Encrypted packets -> <- Encrypted packets
72data ToxProgress
73 = AwaitingDHTKey -- ^ Waiting to receive their DHT key.
74 | AcquiringIPAddress -- ^ Searching DHT to obtain their node's IP & port.
75 | AcquiringCookie -- ^ Attempting to obtain a cookie.
76 | AwaitingHandshake -- ^ Waiting to receive a handshake.
77 | AwaitingSessionPacket -- ^ Connection is "accepted" but not yet "confirmed".
78 deriving (Eq,Ord,Enum,Show)
79
80 24
81data Parameters = Parameters 25data Parameters = Parameters
82 { -- | Various Tox transports and clients. 26 { -- | Various Tox transports and clients.
@@ -87,6 +31,7 @@ data Parameters = Parameters
87 } 31 }
88 32
89data Key = Key NodeId{-me-} NodeId{-them-} 33data Key = Key NodeId{-me-} NodeId{-them-}
34 deriving (Eq,Ord)
90 35
91instance Show Key where show = show . showKey_ 36instance Show Key where show = show . showKey_
92 37
@@ -126,6 +71,16 @@ sessionStatus st = G.Connection
126 , G.connPingLogic = connPingLogic st 71 , G.connPingLogic = connPingLogic st
127 } 72 }
128 73
74lookupForPolicyChange :: TVar (Map.Map Key SessionState)
75 -> Key -> Policy -> IO (Maybe SessionState)
76lookupForPolicyChange conmap k policy = atomically $ do
77 cons <- readTVar conmap
78 fmap join $ forM (Map.lookup k cons) $ \st -> do
79 p <- readTVar (connPolicy st)
80 writeTVar (connPolicy st) policy
81 return $ do
82 guard $ p /= policy
83 return st
129 84
130-- | This function will fork threads as necessary. 85-- | This function will fork threads as necessary.
131setToxPolicy :: Parameters 86setToxPolicy :: Parameters
@@ -135,15 +90,26 @@ setToxPolicy :: Parameters
135 -> IO () 90 -> IO ()
136setToxPolicy params conmap k policy = case policy of 91setToxPolicy params conmap k policy = case policy of
137 TryingToConnect -> do 92 TryingToConnect -> do
138 -- TODO initiate connecting if we haven't already 93 mst <- lookupForPolicyChange conmap k policy
139 -- When established, invoke 'onToxSession'. 94 forM_ mst $ \st -> do
140 return () 95 let getPolicy = readTVar $ connPolicy st
141 RefusingToConnect -> do 96 --TODO accept_thread may already be started if policy was OpenToConnect
142 -- TODO disconnect or cancel any pending connection 97 accept_thread <- forkIO $ acceptContact getPolicy _accept_methods
98 persue_thread <- forkIO $ persueContact getPolicy _get_status _persue_methods
99 freshen_thread <- forkIO $ freshenContact getPolicy _get_status _freshen_methods
100 return ()
143 return () 101 return ()
144 OpenToConnect -> do 102 RefusingToConnect -> do -- disconnect or cancel any pending connection
145 -- TODO passively accept connections if they initiate. 103 mst <- lookupForPolicyChange conmap k policy
104 -- Since the 3 connection threads poll the current policy, they should
105 -- all terminate on their own.
146 return () 106 return ()
107 OpenToConnect -> do -- passively accept connections if they initiate.
108 mst <- lookupForPolicyChange conmap k policy
109 forM_ mst $ \st -> do
110 let getPolicy = readTVar $ connPolicy st
111 accept_thread <- forkIO $ acceptContact getPolicy _accept_methods
112 return ()
147 113
148 114
149showKey_ :: Key -> String 115showKey_ :: Key -> String
diff --git a/Connection/Tox/Threads.hs b/Connection/Tox/Threads.hs
index 8b19c7cf..dcee37d1 100644
--- a/Connection/Tox/Threads.hs
+++ b/Connection/Tox/Threads.hs
@@ -12,7 +12,7 @@
12module Connection.Tox.Threads where 12module Connection.Tox.Threads where
13 13
14import Connection 14import Connection
15import Connection.Tox 15-- import Connection.Tox
16import Data.IP (IP) 16import Data.IP (IP)
17import Network.Tox.Crypto.Transport 17import Network.Tox.Crypto.Transport
18import Network.Tox.NodeId 18import Network.Tox.NodeId
@@ -27,6 +27,70 @@ import Data.Function
27import Data.Functor.Identity 27import Data.Functor.Identity
28import System.Timeout 28import System.Timeout
29 29
30
31-- | This type indicates the progress of a tox encrypted friend link
32-- connection. Two scenarios are illustrated below. The parenthesis show the
33-- current 'G.Status' 'ToxProgress' of the session.
34--
35--
36-- Perfect handshake scenario:
37--
38-- Peer 1 Peer 2
39-- (InProgress AcquiringCookie) (Dormant/InProgress AcquiringCookie)
40-- Cookie request ->
41-- <- Cookie response
42-- (InProgress AwaitingHandshake) (Dormant/InProgress AcquiringCookie)
43-- Handshake packet ->
44-- * accepts connection
45-- (InProgress AwaitingSessionPacket)
46-- <- Handshake packet
47-- *accepts connection
48-- (InProgress AwaitingSessionPacket)
49-- Encrypted packet -> <- Encrypted packet
50-- *confirms connection *confirms connection
51-- (Established) (Established)
52--
53-- Connection successful.
54--
55-- Encrypted packets -> <- Encrypted packets
56--
57--
58--
59--
60-- More realistic handshake scenario:
61-- Peer 1 Peer 2
62-- (InProgress AcquiringCookie) (Dormant/InProgress AcquiringCookie)
63-- Cookie request -> *packet lost*
64-- Cookie request ->
65-- <- Cookie response
66-- (InProgress AwaitingHandshake) (Dormant/InProgress AcquiringCookie)
67--
68-- *Peer 2 randomly starts new connection to peer 1
69-- (InProgress AcquiringCookie)
70-- <- Cookie request
71-- Cookie response ->
72-- (InProgress AwaitingHandshake)
73--
74-- Handshake packet -> <- Handshake packet
75-- *accepts connection * accepts connection
76-- (InProgress AwaitingSessionPacket) (InProgress AwaitingSessionPacket)
77--
78-- Encrypted packet -> <- Encrypted packet
79-- *confirms connection *confirms connection
80-- (Established) (Established)
81--
82-- Connection successful.
83--
84-- Encrypted packets -> <- Encrypted packets
85data ToxProgress
86 = AwaitingDHTKey -- ^ Waiting to receive their DHT key.
87 | AcquiringIPAddress -- ^ Searching DHT to obtain their node's IP & port.
88 | AcquiringCookie -- ^ Attempting to obtain a cookie.
89 | AwaitingHandshake -- ^ Waiting to receive a handshake.
90 | AwaitingSessionPacket -- ^ Connection is "accepted" but not yet "confirmed".
91 deriving (Eq,Ord,Enum,Show)
92
93
30type NodeSearch = Search NodeId (IP,PortNumber) () NodeInfo NodeInfo 94type NodeSearch = Search NodeId (IP,PortNumber) () NodeInfo NodeInfo
31 95
32data AcceptContactMethods = AcceptContactMethods 96data AcceptContactMethods = AcceptContactMethods