summaryrefslogtreecommitdiff
path: root/examples/toxrelay.hs
diff options
context:
space:
mode:
Diffstat (limited to 'examples/toxrelay.hs')
-rw-r--r--examples/toxrelay.hs91
1 files changed, 54 insertions, 37 deletions
diff --git a/examples/toxrelay.hs b/examples/toxrelay.hs
index f03605f9..953b230b 100644
--- a/examples/toxrelay.hs
+++ b/examples/toxrelay.hs
@@ -15,6 +15,7 @@ import qualified Data.Map as Map
15 ;import Data.Map (Map) 15 ;import Data.Map (Map)
16import Data.Serialize 16import Data.Serialize
17import Data.Word 17import Data.Word
18import Network.Socket (SockAddr)
18import System.IO 19import System.IO
19import System.IO.Error 20import System.IO.Error
20import System.Timeout 21import System.Timeout
@@ -26,6 +27,7 @@ import Data.Tox.Relay
26import Network.Address (getBindAddress) 27import Network.Address (getBindAddress)
27import Network.StreamServer 28import Network.StreamServer
28import Network.Tox (newCrypto) 29import Network.Tox (newCrypto)
30import Network.Tox.Onion.Transport hiding (encrypt,decrypt)
29 31
30 32
31 33
@@ -41,9 +43,9 @@ hGetSized h = runGet get <$> B.hGet h len -- We treat parse-fail the same as EOF
41 ConstSize len = size :: Size x 43 ConstSize len = size :: Size x
42 44
43data RelaySession = RelaySession 45data RelaySession = RelaySession
44 { indexPool :: IntSet -- ^ Ints that are either solicited or associated. 46 { indexPool :: IntSet -- ^ Ints that are either solicited or associated.
45 , solicited :: Map PublicKey Int -- ^ Reserved ids, not yet in associated. 47 , solicited :: Map PublicKey Int -- ^ Reserved ids, not yet in associated.
46 , associated :: IntMap (RelayPacket -> IO ()) -- ^ Peers this session is connected to. 48 , associated :: IntMap ((ConId -> RelayPacket) -> IO ()) -- ^ Peers this session is connected to.
47 } 49 }
48 50
49freshSession :: RelaySession 51freshSession :: RelaySession
@@ -63,16 +65,17 @@ disconnect cons who = join $ atomically $ do
63 Just (_,session) -> do 65 Just (_,session) -> do
64 modifyTVar' cons $ Map.delete who 66 modifyTVar' cons $ Map.delete who
65 RelaySession { associated = cs } <- readTVar session 67 RelaySession { associated = cs } <- readTVar session
66 return $ let notifyPeer i send = (send (DisconnectNotification $ key2c i) >>) 68 return $ let notifyPeer i send = ((send DisconnectNotification) >>)
67 in IntMap.foldrWithKey notifyPeer (return ()) cs 69 in IntMap.foldrWithKey notifyPeer (return ()) cs
68 70
69relaySession :: TransportCrypto 71relaySession :: TransportCrypto
70 -> TVar (Map PublicKey (RelayPacket -> IO (),TVar RelaySession)) 72 -> TVar (Map PublicKey (RelayPacket -> IO (),TVar RelaySession))
73 -> (SockAddr -> OnionRequest N1 -> IO ())
71 -> sock 74 -> sock
72 -> Int 75 -> Int
73 -> Handle 76 -> Handle
74 -> IO () 77 -> IO ()
75relaySession crypto cons _ conid h = do 78relaySession crypto cons sendOnion _ conid h = do
76 -- atomically $ modifyTVar' cons $ IntMap.insert conid h 79 -- atomically $ modifyTVar' cons $ IntMap.insert conid h
77 80
78 -- mhello <- fmap (>>= \h -> decryptPayload (computeSharedSecret me (helloFrom h) (helloNonce h)) h) $ hGetSized h 81 -- mhello <- fmap (>>= \h -> decryptPayload (computeSharedSecret me (helloFrom h) (helloNonce h)) h) $ hGetSized h
@@ -98,16 +101,6 @@ relaySession crypto cons _ conid h = do
98 noncef' <- let them' = sessionPublicKey (runIdentity $ helloData hello) 101 noncef' <- let them' = sessionPublicKey (runIdentity $ helloData hello)
99 in lookupNonceFunction crypto me' them' 102 in lookupNonceFunction crypto me' them'
100 103
101 sendPacket <- do
102 v <- newMVar (sessionBaseNonce $ runIdentity $ welcomeData welcome)
103 return $ \p -> do
104 n24 <- takeMVar v
105 let bs = encode $ encrypt (noncef' n24) $ encodePlain (p :: RelayPacket)
106 do B.hPut h $ encode (fromIntegral (B.length bs) :: Word16)
107 B.hPut h bs
108 `catchIOError` \_ -> return ()
109 putMVar v (incrementNonce24 n24)
110
111 let readPacket n24 = (>>= decrypt (noncef' n24) >=> decodePlain) <$> hGetPrefixed h 104 let readPacket n24 = (>>= decrypt (noncef' n24) >=> decodePlain) <$> hGetPrefixed h
112 base = sessionBaseNonce $ runIdentity $ helloData hello 105 base = sessionBaseNonce $ runIdentity $ helloData hello
113 106
@@ -116,33 +109,47 @@ relaySession crypto cons _ conid h = do
116 forM_ mpkt0 $ \pkt0 -> do 109 forM_ mpkt0 $ \pkt0 -> do
117 110
118 disconnect cons (helloFrom hello) 111 disconnect cons (helloFrom hello)
119 session <- atomically $ do 112 (sendPacket,session) <- do
120 session <- newTVar freshSession 113 session <- atomically $ newTVar freshSession
121 modifyTVar' cons $ Map.insert (helloFrom hello) (sendPacket,session) 114 sendPacket <- do
122 return session 115 v <- newMVar (sessionBaseNonce $ runIdentity $ welcomeData welcome)
123 116 return $ \p -> do
124 handlePacket cons (helloFrom hello) sendPacket session pkt0 117 case p of
118 DisconnectNotification con -> atomically $ do
119 modifyTVar' session $ \s -> s
120 { indexPool = maybe id IntSet.delete (c2key con) (indexPool s)
121 , associated = maybe id IntMap.delete (c2key con) (associated s)
122 }
123 _ -> return ()
124 n24 <- takeMVar v
125 let bs = encode $ encrypt (noncef' n24) $ encodePlain (p :: RelayPacket)
126 do B.hPut h $ encode (fromIntegral (B.length bs) :: Word16)
127 B.hPut h bs
128 `catchIOError` \_ -> return ()
129 putMVar v (incrementNonce24 n24)
130 atomically $ modifyTVar' cons $ Map.insert (helloFrom hello) (sendPacket,session)
131 return (sendPacket,session)
132
133 handlePacket cons conid (helloFrom hello) crypto sendOnion sendPacket session pkt0
125 134
126 flip fix (incrementNonce24 base) $ \loop n24 -> do 135 flip fix (incrementNonce24 base) $ \loop n24 -> do
127 m <- readPacket n24 136 m <- readPacket n24
128 forM_ m $ \p -> do 137 forM_ m $ \p -> do
129 handlePacket cons (helloFrom hello) sendPacket session p 138 handlePacket cons conid (helloFrom hello) crypto sendOnion sendPacket session p
130 loop (incrementNonce24 n24) 139 loop (incrementNonce24 n24)
131 `finally` 140 `finally`
132 disconnect cons (helloFrom hello) 141 disconnect cons (helloFrom hello)
133 142
134data R = R { routingRequest :: PublicKey -> IO ConId
135 , reply :: RelayPacket -> IO ()
136 , routeOOB :: PublicKey -> IO (Maybe (RelayPacket -> IO ()))
137 }
138
139handlePacket :: TVar (Map PublicKey (RelayPacket -> IO (), TVar RelaySession)) 143handlePacket :: TVar (Map PublicKey (RelayPacket -> IO (), TVar RelaySession))
144 -> Int
140 -> PublicKey 145 -> PublicKey
146 -> TransportCrypto
147 -> (SockAddr -> OnionRequest N1 -> IO ())
141 -> (RelayPacket -> IO ()) 148 -> (RelayPacket -> IO ())
142 -> TVar RelaySession 149 -> TVar RelaySession
143 -> RelayPacket 150 -> RelayPacket
144 -> IO () 151 -> IO ()
145handlePacket cons me sendToMe session = \case 152handlePacket cons thistcp me crypto sendOnion sendToMe session = \case
146 RoutingRequest them -> join $ atomically $ do 153 RoutingRequest them -> join $ atomically $ do
147 mySession <- readTVar session 154 mySession <- readTVar session
148 mi <- case Map.lookup them (solicited mySession) of 155 mi <- case Map.lookup them (solicited mySession) of
@@ -161,16 +168,18 @@ handlePacket cons me sendToMe session = \case
161 forM mp $ \(sendToThem,peer) -> do 168 forM mp $ \(sendToThem,peer) -> do
162 theirSession <- readTVar peer 169 theirSession <- readTVar peer
163 forM (Map.lookup me $ solicited theirSession) $ \reserved_id -> do 170 forM (Map.lookup me $ solicited theirSession) $ \reserved_id -> do
171 let sendToThem' f = sendToThem $ f $ key2c reserved_id
172 sendToMe' f = sendToMe $ f $ key2c i
164 writeTVar peer theirSession 173 writeTVar peer theirSession
165 { solicited = Map.delete me (solicited theirSession) 174 { solicited = Map.delete me (solicited theirSession)
166 , associated = IntMap.insert reserved_id sendToMe (associated theirSession) 175 , associated = IntMap.insert reserved_id sendToMe' (associated theirSession)
167 } 176 }
168 writeTVar session mySession 177 writeTVar session mySession
169 { solicited = Map.delete them (solicited mySession) 178 { solicited = Map.delete them (solicited mySession)
170 , associated = IntMap.insert i sendToThem (associated mySession) 179 , associated = IntMap.insert i sendToThem' (associated mySession)
171 } 180 }
172 return $ do sendToThem $ ConnectNotification (key2c reserved_id) 181 return $ do sendToThem' ConnectNotification
173 sendToMe $ ConnectNotification (key2c i) 182 sendToMe' ConnectNotification
174 return $ do sendToMe $ RoutingResponse (maybe badcon key2c mi) them 183 return $ do sendToMe $ RoutingResponse (maybe badcon key2c mi) them
175 sequence_ notifyConnect 184 sequence_ notifyConnect
176 185
@@ -180,7 +189,7 @@ handlePacket cons me sendToMe session = \case
180 m <- atomically $ Map.lookup them <$> readTVar cons 189 m <- atomically $ Map.lookup them <$> readTVar cons
181 forM_ m $ \(sendToThem,_) -> sendToThem $ OOBRecv me bs 190 forM_ m $ \(sendToThem,_) -> sendToThem $ OOBRecv me bs
182 191
183 RelayData con bs -> join $ atomically $ do 192 RelayData bs con -> join $ atomically $ do
184 -- Data: Data packets can only be sent and received if the 193 -- Data: Data packets can only be sent and received if the
185 -- corresponding connection_id is connection (a Connect notification 194 -- corresponding connection_id is connection (a Connect notification
186 -- has been received from it) if the server receives a Data packet for 195 -- has been received from it) if the server receives a Data packet for
@@ -188,8 +197,14 @@ handlePacket cons me sendToMe session = \case
188 mySession <- readTVar session 197 mySession <- readTVar session
189 return $ sequence_ $ do 198 return $ sequence_ $ do
190 i <- c2key con 199 i <- c2key con
191 sendToThem <- IntMap.lookup i $ associated mySession 200 sendToThem' <- IntMap.lookup i $ associated mySession
192 return $ sendToThem $ RelayData _todo bs 201 return $ sendToThem' $ RelayData bs
202
203 OnionPacket p -> do
204 mp <- rewrap crypto (TCPIndex thistcp) p
205 case mp of
206 Right (p',addr) -> sendOnion addr p'
207 _ -> return ()
193 208
194 _ -> return () 209 _ -> return ()
195 210
@@ -199,9 +214,11 @@ main = do
199 crypto <- newCrypto 214 crypto <- newCrypto
200 cons <- newTVarIO Map.empty 215 cons <- newTVarIO Map.empty
201 a <- getBindAddress "33445" True 216 a <- getBindAddress "33445" True
217 let sendOnion :: SockAddr -> OnionRequest N1 -> IO ()
218 sendOnion _ _ = return ()
202 h <- streamServer ServerConfig 219 h <- streamServer ServerConfig
203 { serverWarn = hPutStrLn stderr 220 { serverWarn = hPutStrLn stderr
204 , serverSession = relaySession crypto cons 221 , serverSession = relaySession crypto cons sendOnion
205 } 222 }
206 a 223 a
207 224