diff options
Diffstat (limited to 'examples')
-rw-r--r-- | examples/testTox.hs | 79 |
1 files changed, 53 insertions, 26 deletions
diff --git a/examples/testTox.hs b/examples/testTox.hs index 5314024f..cc8bd45f 100644 --- a/examples/testTox.hs +++ b/examples/testTox.hs | |||
@@ -1,6 +1,7 @@ | |||
1 | {-# LANGUAGE NamedFieldPuns #-} | 1 | {-# LANGUAGE NamedFieldPuns #-} |
2 | {-# LANGUAGE CPP #-} | 2 | {-# LANGUAGE CPP #-} |
3 | {-# LANGUAGE OverloadedStrings #-} | 3 | {-# LANGUAGE OverloadedStrings #-} |
4 | {-# LANGUAGE LambdaCase #-} | ||
4 | #ifdef THREAD_DEBUG | 5 | #ifdef THREAD_DEBUG |
5 | import Control.Concurrent.Lifted.Instrument | 6 | import Control.Concurrent.Lifted.Instrument |
6 | #else | 7 | #else |
@@ -9,18 +10,19 @@ import Control.Concurrent.Lifted | |||
9 | import Control.Concurrent.STM.TChan | 10 | import Control.Concurrent.STM.TChan |
10 | import Control.Concurrent.STM.TMChan | 11 | import Control.Concurrent.STM.TMChan |
11 | import Control.Concurrent.STM.TVar | 12 | import Control.Concurrent.STM.TVar |
12 | import Control.Concurrent.Supply | ||
13 | import Control.Monad | 13 | import Control.Monad |
14 | import Control.Monad.STM | 14 | import Control.Monad.STM |
15 | import Crypto.Tox | 15 | import Crypto.Tox |
16 | import qualified Data.IntMap.Strict as IntMap | 16 | import qualified Data.IntMap.Strict as IntMap |
17 | import Data.Function | ||
17 | import DebugUtil | 18 | import DebugUtil |
18 | import DPut | 19 | import DPut |
20 | import HandshakeCache | ||
19 | import Network.QueryResponse | 21 | import Network.QueryResponse |
20 | import Network.Socket | 22 | import Network.Socket |
21 | import Network.Tox | 23 | import Network.Tox |
22 | import Network.Tox.ContactInfo | 24 | import Network.Tox.ContactInfo |
23 | import qualified Network.Tox.Crypto.Handlers as CH | 25 | import Network.Tox.Session |
24 | import Network.Tox.Crypto.Transport | 26 | import Network.Tox.Crypto.Transport |
25 | import Network.Tox.DHT.Handlers as DHT | 27 | import Network.Tox.DHT.Handlers as DHT |
26 | import Network.Tox.DHT.Transport | 28 | import Network.Tox.DHT.Transport |
@@ -33,12 +35,14 @@ import Data.Time.Clock.POSIX | |||
33 | import System.Exit | 35 | import System.Exit |
34 | 36 | ||
35 | 37 | ||
36 | makeToxNode :: UDPTransport -> Maybe SecretKey -> IO (Tox extra) | 38 | makeToxNode :: UDPTransport -> Maybe SecretKey |
37 | makeToxNode udp sec = do | 39 | -> ( ContactInfo extra -> SockAddr -> Session -> IO () ) |
40 | -> IO (Tox extra) | ||
41 | makeToxNode udp sec onSessionF = do | ||
38 | keysdb <- newKeysDatabase | 42 | keysdb <- newKeysDatabase |
39 | newToxOverTransport keysdb | 43 | newToxOverTransport keysdb |
40 | (SockAddrInet 0 0) | 44 | (SockAddrInet 0 0) |
41 | Nothing | 45 | onSessionF |
42 | sec | 46 | sec |
43 | udp | 47 | udp |
44 | 48 | ||
@@ -46,18 +50,33 @@ makeToxNode udp sec = do | |||
46 | setToxID :: Tox () -> Maybe SecretKey -> IO () | 50 | setToxID :: Tox () -> Maybe SecretKey -> IO () |
47 | setToxID tox (Just sec) = atomically $ addContactInfo (toxContactInfo tox) sec () | 51 | setToxID tox (Just sec) = atomically $ addContactInfo (toxContactInfo tox) sec () |
48 | 52 | ||
49 | sessionChan :: Tox extra -> IO (TChan (TMChan CryptoMessage)) | 53 | sessionChan :: TVar (Map.Map PublicKey [Session]) -> TChan (TMChan CryptoMessage) |
50 | sessionChan Tox{toxCryptoSessions} = do | 54 | -> ContactInfo extra -> SockAddr -> Session -> IO () |
51 | tchan <- atomically newTChan | 55 | sessionChan remotes tchan acnt saddr s = do |
52 | atomically $ CH.addNewSessionHook toxCryptoSessions $ \_ nc -> do | 56 | ch <- atomically $ do |
53 | atomically $ do | 57 | modifyTVar' remotes $ (`Map.alter` sTheirUserKey s) $ \case |
54 | session_chan <- newTMChan | 58 | Just ss -> Just (s : ss) |
55 | writeTChan tchan session_chan | 59 | Nothing -> Just [s] |
56 | (n,supply) <- freshId <$> readTVar (CH.listenerIDSupply toxCryptoSessions) | 60 | session_chan <- newTMChan |
57 | writeTVar (CH.listenerIDSupply toxCryptoSessions) supply | 61 | writeTChan tchan session_chan |
58 | modifyTVar' (CH.ncListeners nc) $ IntMap.insert n (0,session_chan) | 62 | return session_chan |
59 | return Nothing | 63 | let onPacket loop Nothing = return () |
60 | return tchan | 64 | onPacket loop (Just (Left e)) = dput XUnused e >> loop |
65 | onPacket loop (Just (Right (x,()))) = do | ||
66 | atomically $ writeTMChan ch x | ||
67 | loop | ||
68 | -- forkIO $ fix $ awaitMessage (sTransport s) . onPacket | ||
69 | return () | ||
70 | |||
71 | netCrypto :: Tox extra -> SecretKey -> NodeInfo -> PublicKey -> IO () | ||
72 | netCrypto tox me ni them = do | ||
73 | mcookie <- cookieRequest (toxCryptoKeys tox) (toxDHT tox) (toPublic me) ni | ||
74 | case mcookie of | ||
75 | Just cookie -> do | ||
76 | hs <- cacheHandshake (toxHandshakeCache tox) me them ni cookie | ||
77 | sendMessage (toxHandshakes tox) (nodeAddr ni) hs | ||
78 | Nothing -> do | ||
79 | dput XUnused "Timeout requesting cookie." | ||
61 | 80 | ||
62 | 81 | ||
63 | main :: IO () | 82 | main :: IO () |
@@ -67,22 +86,28 @@ main = do | |||
67 | 86 | ||
68 | (udpA,udpB) <- testPairTransport | 87 | (udpA,udpB) <- testPairTransport |
69 | 88 | ||
89 | a_remotes <- atomically (newTVar Map.empty) | ||
90 | a_sessions <- atomically newTChan | ||
70 | a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf | 91 | a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf |
71 | <- makeToxNode udpA $ decodeSecret "YrJQFG7Xppg4WAyhooONNGSCRVQbrRF9L4VoQQsetF" | 92 | <- makeToxNode udpA (decodeSecret "YrJQFG7Xppg4WAyhooONNGSCRVQbrRF9L4VoQQsetF") |
93 | (sessionChan a_remotes a_sessions) | ||
72 | a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf | 94 | a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf |
73 | `setToxID` -- BDDj3maMmK8hR3mTpju29wmtE2YJ5cf8NlNEWi1dXlI | 95 | `setToxID` -- BDDj3maMmK8hR3mTpju29wmtE2YJ5cf8NlNEWi1dXlI |
74 | decodeSecret "UdZUB9Mf1RD3pVGh02OsRJM6YpmGqJiVxYGVIVHkAG" | 96 | decodeSecret "UdZUB9Mf1RD3pVGh02OsRJM6YpmGqJiVxYGVIVHkAG" |
75 | 97 | ||
76 | a_sessions <- sessionChan a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf | 98 | -- a_sessions <- sessionChan a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf |
77 | 99 | ||
100 | b_remotes <- atomically (newTVar Map.empty) | ||
101 | b_sessions <- atomically newTChan | ||
78 | let b = read "OM7znaPMYkTbm.9GcZJAdnDATXmZxZ9fnaSTP3qNCZk@2.0.0.0:2" | 102 | let b = read "OM7znaPMYkTbm.9GcZJAdnDATXmZxZ9fnaSTP3qNCZk@2.0.0.0:2" |
79 | b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk | 103 | b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk |
80 | <- makeToxNode udpB $ decodeSecret "Lm2pnsu1+80I8h9txMoZyGgcNwfaoqBlIfg5TwWUXL" | 104 | <- makeToxNode udpB (decodeSecret "Lm2pnsu1+80I8h9txMoZyGgcNwfaoqBlIfg5TwWUXL") |
105 | (sessionChan b_remotes b_sessions) | ||
81 | b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk | 106 | b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk |
82 | `setToxID` -- AvETKhO-YqnNRopZrj8K3xUpGtGbX0sLhZZjh2VufJB | 107 | `setToxID` -- AvETKhO-YqnNRopZrj8K3xUpGtGbX0sLhZZjh2VufJB |
83 | decodeSecret "L7WNtNIbm0ajNlPrkWvSRpn0nypTUZxlHBckZPlTje" | 108 | decodeSecret "L7WNtNIbm0ajNlPrkWvSRpn0nypTUZxlHBckZPlTje" |
84 | 109 | ||
85 | b_sessions <- sessionChan b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk | 110 | -- b_sessions <- sessionChan b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk |
86 | 111 | ||
87 | (a_quit,_,_) <- forkTox a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf False | 112 | (a_quit,_,_) <- forkTox a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf False |
88 | (b_quit,_,_) <- forkTox b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk False | 113 | (b_quit,_,_) <- forkTox b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk False |
@@ -125,23 +150,25 @@ main = do | |||
125 | forkIO $ do | 150 | forkIO $ do |
126 | tid <- myThreadId | 151 | tid <- myThreadId |
127 | labelThread tid "testToxLaunch" | 152 | labelThread tid "testToxLaunch" |
128 | void $ netCrypto a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf a_secret b_public | 153 | netCrypto a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf a_secret b b_public |
129 | dput XUnused "REACHEDREACHEDREACHEDREACHED" | 154 | dput XUnused "REACHEDREACHEDREACHEDREACHED" |
130 | dput XUnused "REACHEDREACHEDREACHEDREACHED" | 155 | dput XUnused "REACHEDREACHEDREACHEDREACHED" |
131 | dput XUnused "REACHEDREACHEDREACHEDREACHED" | 156 | dput XUnused "REACHEDREACHEDREACHEDREACHED" |
132 | threadDelay 1000000 | 157 | threadDelay 1000000 |
133 | -- a says "Howdy" | 158 | -- a says "Howdy" |
134 | mp_a <- atomically . readTVar $ CH.netCryptoSessionsByKey (toxCryptoSessions a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf) | 159 | mp_a <- atomically . readTVar $ a_remotes |
135 | case Map.lookup b_public mp_a of | 160 | case Map.lookup b_public mp_a of |
136 | Just [session] -> do | 161 | Just [session] -> do |
137 | dput XUnused "----------------- HOWDY ---------------" | 162 | dput XUnused "----------------- HOWDY ---------------" |
138 | CH.sendChatMsg (toxCryptoKeys a_Ct7g5azVcJ8KnvxzbXs9GqeqcjrP7VdZXIC'uHeTlRf) session "Howdy" | 163 | sendMessage (sTransport session) () (UpToN MESSAGE "Howdy") |
164 | Just xs -> dput XUnused "Unexpectedly a has TOO MANY sesions for b" | ||
165 | Nothing -> dput XUnused "Unexpectedly a has NO session for b" | ||
139 | -- b says "Hey you!" | 166 | -- b says "Hey you!" |
140 | mp_b <- atomically . readTVar $ CH.netCryptoSessionsByKey (toxCryptoSessions b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk) | 167 | mp_b <- atomically . readTVar $ b_remotes |
141 | case Map.lookup a_public mp_b of | 168 | case Map.lookup a_public mp_b of |
142 | Just [session] -> do | 169 | Just [session] -> do |
143 | dput XUnused "----------------- HEY YOU ---------------" | 170 | dput XUnused "----------------- HEY YOU ---------------" |
144 | void $ CH.sendChatMsg (toxCryptoKeys b_OM7znaPMYkTbm'9GcZJAdnDATXmZxZ9fnaSTP3qNCZk) session "Hey you!" | 171 | sendMessage (sTransport session) () (UpToN MESSAGE "Hey you!") |
145 | Just xs -> dput XUnused "Unexpectedly b has TOO MANY sesions for a" | 172 | Just xs -> dput XUnused "Unexpectedly b has TOO MANY sesions for a" |
146 | Nothing -> dput XUnused "Unexpectedly b has NO session for a" | 173 | Nothing -> dput XUnused "Unexpectedly b has NO session for a" |
147 | 174 | ||