diff options
Diffstat (limited to 'Connection/Tox.hs')
-rw-r--r-- | Connection/Tox.hs | 48 |
1 files changed, 36 insertions, 12 deletions
diff --git a/Connection/Tox.hs b/Connection/Tox.hs index 2c485edd..436e7599 100644 --- a/Connection/Tox.hs +++ b/Connection/Tox.hs | |||
@@ -1,21 +1,25 @@ | |||
1 | {-# LANGUAGE CPP #-} | 1 | {-# LANGUAGE CPP #-} |
2 | {-# LANGUAGE GADTs #-} | 2 | {-# LANGUAGE GADTs #-} |
3 | {-# LANGUAGE NamedFieldPuns #-} | ||
3 | module Connection.Tox | 4 | module Connection.Tox |
4 | ( module Connection.Tox | 5 | ( module Connection.Tox |
5 | , ToxProgress(..) | 6 | , ToxProgress(..) |
6 | ) where | 7 | ) where |
7 | 8 | ||
8 | import qualified Connection as G | 9 | import qualified Connection as G |
9 | ;import Connection (Manager (..), Policy (..)) | 10 | ;import Connection (Manager (..), Policy (..)) |
11 | import Connection.Tox.Threads | ||
10 | import Control.Concurrent.STM | 12 | import Control.Concurrent.STM |
11 | import Control.Monad | 13 | import Control.Monad |
12 | -- import Data.Dependent.Sum | 14 | import Crypto.Tox |
13 | import Data.Functor.Identity | 15 | import Data.Functor.Identity |
14 | import qualified Data.Map as Map | 16 | import qualified Data.HashMap.Strict as HashMap |
15 | import Connection.Tox.Threads | 17 | import qualified Data.Map as Map |
16 | import Network.Tox.NodeId | 18 | import Network.Tox.ContactInfo |
17 | import Network.Tox.DHT.Handlers | ||
18 | import Network.Tox.Crypto.Handlers | 19 | import Network.Tox.Crypto.Handlers |
20 | import Network.Tox.DHT.Handlers as DHT | ||
21 | import Network.Tox.DHT.Transport as DHT | ||
22 | import Network.Tox.NodeId | ||
19 | import PingMachine | 23 | import PingMachine |
20 | import Text.Read | 24 | import Text.Read |
21 | #ifdef THREAD_DEBUG | 25 | #ifdef THREAD_DEBUG |
@@ -24,7 +28,7 @@ import Control.Concurrent.Lifted.Instrument | |||
24 | import Control.Concurrent.Lifted | 28 | import Control.Concurrent.Lifted |
25 | import GHC.Conc (labelThread) | 29 | import GHC.Conc (labelThread) |
26 | #endif | 30 | #endif |
27 | import GHC.Conc (threadStatus,ThreadStatus(..)) | 31 | import GHC.Conc (ThreadStatus (..), threadStatus) |
28 | 32 | ||
29 | 33 | ||
30 | 34 | ||
@@ -32,6 +36,9 @@ import GHC.Conc (threadStatus,ThreadStatus(..)) | |||
32 | data Parameters = Parameters | 36 | data Parameters = Parameters |
33 | { -- | Various Tox transports and clients. | 37 | { -- | Various Tox transports and clients. |
34 | dhtRouting :: Routing | 38 | dhtRouting :: Routing |
39 | , roster :: ContactInfo | ||
40 | , sessions :: NetCryptoSessions | ||
41 | , dhtClient :: DHT.Client | ||
35 | -- | Thread to be forked when a connection is established. | 42 | -- | Thread to be forked when a connection is established. |
36 | -- TODO: this function should accept relevant parameters. | 43 | -- TODO: this function should accept relevant parameters. |
37 | , onToxSession :: IO () | 44 | , onToxSession :: IO () |
@@ -113,22 +120,38 @@ lookupForPolicyChange conmap k policy = atomically $ do | |||
113 | callbackId :: Int | 120 | callbackId :: Int |
114 | callbackId = 1 | 121 | callbackId = 1 |
115 | 122 | ||
123 | lookupContact :: Key -> ContactInfo -> STM (Maybe (SecretKey,Contact)) | ||
124 | lookupContact (Key me them) ContactInfo{accounts} = do | ||
125 | acnts <- readTVar accounts | ||
126 | fmap join $ forM (HashMap.lookup me acnts) $ \Account{userSecret,contacts} -> do | ||
127 | cs <- readTVar contacts | ||
128 | forM (HashMap.lookup them cs) $ \c -> do | ||
129 | return (userSecret,c) | ||
130 | |||
116 | -- | This function will fork threads as necessary. | 131 | -- | This function will fork threads as necessary. |
117 | setToxPolicy :: Parameters | 132 | setToxPolicy :: Parameters |
118 | -> TVar (Map.Map Key SessionState) | 133 | -> TVar (Map.Map Key SessionState) |
119 | -> Key | 134 | -> Key |
120 | -> Policy | 135 | -> Policy |
121 | -> IO () | 136 | -> IO () |
122 | setToxPolicy params conmap k policy = case policy of | 137 | setToxPolicy params conmap k@(Key me them) policy = case policy of |
123 | TryingToConnect -> do | 138 | TryingToConnect -> do |
124 | mst <- lookupForPolicyChange conmap k policy | 139 | mst <- lookupForPolicyChange conmap k policy |
140 | r <- atomically $ lookupContact k (roster params) | ||
141 | forM_ r $ \(sec,c) -> do | ||
125 | let accept_methods = AcceptContactMethods | 142 | let accept_methods = AcceptContactMethods |
126 | { getHandshake = retry -- :: STM (Handshake Identity) | 143 | { getHandshake = retry -- :: STM (Handshake Identity) |
127 | , handshakeIsSuitable = (\_ -> return False) -- :: Handshake Identity -> STM Bool | 144 | , handshakeIsSuitable = (\_ -> return False) -- :: Handshake Identity -> STM Bool |
128 | , transitionToState = (\_ -> return ()) :: G.Status ToxProgress -> STM () | 145 | , transitionToState = (\_ -> return ()) :: G.Status ToxProgress -> STM () |
129 | } | 146 | } |
130 | persue_methods = PersueContactMethods | 147 | persue_methods = PersueContactMethods |
131 | { -- TODO | 148 | { allsessions = sessions params |
149 | , myseckey = sec | ||
150 | , theirpubkey = id2key them | ||
151 | , client = dhtClient params | ||
152 | , shortRetryInterval = _todo | ||
153 | , longRetryInterval = _todo | ||
154 | , contact = c | ||
132 | } | 155 | } |
133 | freshen_methods = FreshenContactMethods | 156 | freshen_methods = FreshenContactMethods |
134 | { dhtkeyInterval = _todo :: Int | 157 | { dhtkeyInterval = _todo :: Int |
@@ -138,6 +161,7 @@ setToxPolicy params conmap k policy = case policy of | |||
138 | , getSockAddr = retry -- :: STM (Maybe SockAddr) | 161 | , getSockAddr = retry -- :: STM (Maybe SockAddr) |
139 | , getBuckets = retry -- :: STM (BucketList NodeInfo) | 162 | , getBuckets = retry -- :: STM (BucketList NodeInfo) |
140 | } | 163 | } |
164 | get_status = readTVar (ncState _todo) | ||
141 | forM_ mst $ \st -> do | 165 | forM_ mst $ \st -> do |
142 | let getPolicy = readTVar $ connPolicy st | 166 | let getPolicy = readTVar $ connPolicy st |
143 | tasks <- atomically $ readTVar (sessionTasks st) | 167 | tasks <- atomically $ readTVar (sessionTasks st) |