summaryrefslogtreecommitdiff
path: root/src/Network
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network')
-rw-r--r--src/Network/BitTorrent/MainlineDHT.hs4
-rw-r--r--src/Network/QueryResponse.hs47
-rw-r--r--src/Network/Tox.hs44
-rw-r--r--src/Network/Tox/DHT/Handlers.hs26
-rw-r--r--src/Network/Tox/NodeId.hs5
-rw-r--r--src/Network/Tox/Onion/Handlers.hs81
-rw-r--r--src/Network/Tox/Onion/Transport.hs61
7 files changed, 186 insertions, 82 deletions
diff --git a/src/Network/BitTorrent/MainlineDHT.hs b/src/Network/BitTorrent/MainlineDHT.hs
index 4566471a..f4ce4019 100644
--- a/src/Network/BitTorrent/MainlineDHT.hs
+++ b/src/Network/BitTorrent/MainlineDHT.hs
@@ -584,7 +584,7 @@ newClient swarms addr = do
584 gen cnt = (TransactionId $ S.encode cnt, cnt+1) 584 gen cnt = (TransactionId $ S.encode cnt, cnt+1)
585 585
586 client = Client 586 client = Client
587 { clientNet = addHandler (handleMessage client) net 587 { clientNet = addHandler ignoreErrors (handleMessage client) net
588 , clientDispatcher = dispatch 588 , clientDispatcher = dispatch
589 , clientErrorReporter = ignoreErrors -- printErrors stderr 589 , clientErrorReporter = ignoreErrors -- printErrors stderr
590 , clientPending = map_var 590 , clientPending = map_var
@@ -1002,7 +1002,7 @@ mainlineSend meth unwrap msg client nid addr = do
1002 return $ join $ either (const Nothing) Just <$> reply 1002 return $ join $ either (const Nothing) Just <$> reply
1003 where 1003 where
1004 serializer = MethodSerializer 1004 serializer = MethodSerializer
1005 { methodTimeout = 5 1005 { methodTimeout = \_ ni -> return (ni, 5000000)
1006 , method = meth 1006 , method = meth
1007 , wrapQuery = encodeQueryPayload meth (isReadonlyClient client) 1007 , wrapQuery = encodeQueryPayload meth (isReadonlyClient client)
1008 , unwrapResponse = (>>= either (Left . Error GenericError . C8.pack) 1008 , unwrapResponse = (>>= either (Left . Error GenericError . C8.pack)
diff --git a/src/Network/QueryResponse.hs b/src/Network/QueryResponse.hs
index 0fa1a05a..70d981e2 100644
--- a/src/Network/QueryResponse.hs
+++ b/src/Network/QueryResponse.hs
@@ -108,18 +108,18 @@ partitionTransportM parse encodex tr = do
108 } 108 }
109 return (xtr, ytr) 109 return (xtr, ytr)
110 110
111addHandler :: (addr -> x -> IO (Maybe (x -> x))) -> Transport err addr x -> Transport err addr x 111addHandler :: ErrorReporter addr x meth tid err -> (addr -> x -> IO (Maybe (x -> x))) -> Transport err addr x -> Transport err addr x
112addHandler f tr = tr 112addHandler err f tr = tr
113 { awaitMessage = \kont -> fix $ \eat -> awaitMessage tr $ \m -> do 113 { awaitMessage = \kont -> fix $ \eat -> awaitMessage tr $ \m -> do
114 case m of 114 case m of
115 Just (Right (x, addr)) -> f addr x >>= maybe eat (kont . Just . Right . (, addr) . ($ x)) 115 Just (Right (x, addr)) -> f addr x >>= maybe eat (kont . Just . Right . (, addr) . ($ x))
116 Just (Left e ) -> kont $ Just (Left e) 116 Just (Left e ) -> reportParseError err e >> kont (Just $ Left e)
117 Nothing -> kont $ Nothing 117 Nothing -> kont $ Nothing
118 } 118 }
119 119
120-- | Modify a 'Transport' to invoke an action upon every received packet. 120-- | Modify a 'Transport' to invoke an action upon every received packet.
121onInbound :: (addr -> x -> IO ()) -> Transport err addr x -> Transport err addr x 121onInbound :: (addr -> x -> IO ()) -> Transport err addr x -> Transport err addr x
122onInbound f tr = addHandler (\addr x -> f addr x >> return (Just id)) tr 122onInbound f tr = addHandler ignoreErrors (\addr x -> f addr x >> return (Just id)) tr
123 123
124-- * Using a query\/response client. 124-- * Using a query\/response client.
125 125
@@ -153,16 +153,17 @@ sendQuery ::
153 -> a -- ^ The outbound query. 153 -> a -- ^ The outbound query.
154 -> addr -- ^ Destination address of query. 154 -> addr -- ^ Destination address of query.
155 -> IO (Maybe b) -- ^ The response, or 'Nothing' if it timed out. 155 -> IO (Maybe b) -- ^ The response, or 'Nothing' if it timed out.
156sendQuery (Client net d err pending whoami _) meth q addr = do 156sendQuery (Client net d err pending whoami _) meth q addr0 = do
157 mvar <- newEmptyMVar 157 mvar <- newEmptyMVar
158 tid <- atomically $ do 158 (tid,addr,expiry) <- atomically $ do
159 tbl <- readTVar pending 159 tbl <- readTVar pending
160 (tid, tbl') <- dispatchRegister (tableMethods d) mvar tbl 160 (tid, tbl') <- dispatchRegister (tableMethods d) mvar addr0 tbl
161 (addr,expiry) <- methodTimeout meth tid addr0
161 writeTVar pending tbl' 162 writeTVar pending tbl'
162 return tid 163 return (tid,addr,expiry)
163 self <- whoami (Just addr) 164 self <- whoami (Just addr)
164 sendMessage net addr (wrapQuery meth tid self addr q) 165 sendMessage net addr (wrapQuery meth tid self addr q)
165 mres <- timeout (1000000 * methodTimeout meth) $ takeMVar mvar 166 mres <- timeout expiry $ takeMVar mvar
166 case mres of 167 case mres of
167 Just x -> return $ Just $ unwrapResponse meth x 168 Just x -> return $ Just $ unwrapResponse meth x
168 Nothing -> do 169 Nothing -> do
@@ -248,8 +249,10 @@ dispatchQuery (NoReply unwrapQ f) tid self x addr =
248-- peer-to-peer algorithm will define a 'MethodSerializer' for every 'MethodHandler' that 249-- peer-to-peer algorithm will define a 'MethodSerializer' for every 'MethodHandler' that
249-- might be returned by 'lookupHandler'. 250-- might be returned by 'lookupHandler'.
250data MethodSerializer tid addr x meth a b = MethodSerializer 251data MethodSerializer tid addr x meth a b = MethodSerializer
251 { -- | Seconds to wait for a response. 252 { -- | Returns the microseconds to wait for a response to this query being
252 methodTimeout :: Int 253 -- sent to the given address. The /addr/ may also be modified to add
254 -- routing information.
255 methodTimeout :: tid -> addr -> STM (addr,Int)
253 -- | A method identifier used for error reporting. This needn't be the 256 -- | A method identifier used for error reporting. This needn't be the
254 -- same as the /meth/ argument to 'MethodHandler', but it is suggested. 257 -- same as the /meth/ argument to 'MethodHandler', but it is suggested.
255 , method :: meth 258 , method :: meth
@@ -269,13 +272,13 @@ data MethodSerializer tid addr x meth a b = MethodSerializer
269-- 272--
270-- The type variable /d/ is used to represent the current state of the 273-- The type variable /d/ is used to represent the current state of the
271-- transaction generator and the table of pending transactions. 274-- transaction generator and the table of pending transactions.
272data TransactionMethods d tid x = TransactionMethods 275data TransactionMethods d tid addr x = TransactionMethods
273 { 276 {
274 -- | Before a query is sent, this function stores an 'MVar' to which the 277 -- | Before a query is sent, this function stores an 'MVar' to which the
275 -- response will be written too. The returned /tid/ is a transaction id 278 -- response will be written too. The returned /tid/ is a transaction id
276 -- that can be used to forget the 'MVar' if the remote peer is not 279 -- that can be used to forget the 'MVar' if the remote peer is not
277 -- responding. 280 -- responding.
278 dispatchRegister :: MVar x -> d -> STM (tid, d) 281 dispatchRegister :: MVar x -> addr -> d -> STM (tid, d)
279 -- | This method is invoked when an incoming packet /x/ indicates it is 282 -- | This method is invoked when an incoming packet /x/ indicates it is
280 -- a response to the transaction with id /tid/. The returned IO action 283 -- a response to the transaction with id /tid/. The returned IO action
281 -- is will write the packet to the correct 'MVar' thus completing the 284 -- is will write the packet to the correct 'MVar' thus completing the
@@ -318,27 +321,15 @@ instance Contravariant (TableMethods t) where
318 (\k t -> del (f k) t) 321 (\k t -> del (f k) t)
319 (\k t -> lookup (f k) t) 322 (\k t -> lookup (f k) t)
320 323
321-- | Since 'Int' may be 32 or 64 bits, this function is provided as a
322-- convenience to test if an integral type, such as 'Data.Word.Word64', can be
323-- safely transformed into an 'Int' for use with 'IntMap'.
324--
325-- Returns 'True' if the proxied type can be losslessly converted to 'Int' using
326-- 'fromIntegral'.
327fitsInInt :: forall word. (Bounded word, Integral word) => Proxy word -> Bool
328fitsInInt Proxy = (original == casted)
329 where
330 original = div maxBound 2 :: word
331 casted = fromIntegral (fromIntegral original :: Int) :: word
332
333-- | Construct 'TransactionMethods' methods out of 3 lookup table primitives and a 324-- | Construct 'TransactionMethods' methods out of 3 lookup table primitives and a
334-- function for generating unique transaction ids. 325-- function for generating unique transaction ids.
335transactionMethods :: 326transactionMethods ::
336 TableMethods t tid -- ^ Table methods to lookup values by /tid/. 327 TableMethods t tid -- ^ Table methods to lookup values by /tid/.
337 -> (g -> (tid,g)) -- ^ Generate a new unique /tid/ value and update the generator state /g/. 328 -> (g -> (tid,g)) -- ^ Generate a new unique /tid/ value and update the generator state /g/.
338 -> TransactionMethods (g,t (MVar x)) tid x 329 -> TransactionMethods (g,t (MVar x)) tid addr x
339transactionMethods (TableMethods insert delete lookup) generate = TransactionMethods 330transactionMethods (TableMethods insert delete lookup) generate = TransactionMethods
340 { dispatchCancel = \tid (g,t) -> return (g, delete tid t) 331 { dispatchCancel = \tid (g,t) -> return (g, delete tid t)
341 , dispatchRegister = \v (g,t) -> 332 , dispatchRegister = \v _ (g,t) ->
342 let (tid,g') = generate g 333 let (tid,g') = generate g
343 t' = insert tid v t 334 t' = insert tid v t
344 in return ( tid, (g',t') ) 335 in return ( tid, (g',t') )
@@ -356,7 +347,7 @@ data DispatchMethods tbl err meth tid addr x = DispatchMethods
356 -- | Lookup the handler for a inbound query. 347 -- | Lookup the handler for a inbound query.
357 , lookupHandler :: meth -> Maybe (MethodHandler err tid addr x) 348 , lookupHandler :: meth -> Maybe (MethodHandler err tid addr x)
358 -- | Methods for handling incoming responses. 349 -- | Methods for handling incoming responses.
359 , tableMethods :: TransactionMethods tbl tid x 350 , tableMethods :: TransactionMethods tbl tid addr x
360 } 351 }
361 352
362-- | These methods indicate what should be done upon various conditions. Write 353-- | These methods indicate what should be done upon various conditions. Write
diff --git a/src/Network/Tox.hs b/src/Network/Tox.hs
index 7814046e..3860d309 100644
--- a/src/Network/Tox.hs
+++ b/src/Network/Tox.hs
@@ -21,6 +21,7 @@ import Control.Arrow
21import Control.Concurrent (MVar) 21import Control.Concurrent (MVar)
22import Control.Concurrent.STM 22import Control.Concurrent.STM
23import Control.Monad 23import Control.Monad
24import Control.Monad.Fix
24import qualified Crypto.Cipher.ChaChaPoly1305 as Symmetric 25import qualified Crypto.Cipher.ChaChaPoly1305 as Symmetric
25import qualified Crypto.Cipher.Salsa as Salsa 26import qualified Crypto.Cipher.Salsa as Salsa
26import qualified Crypto.Cipher.XSalsa as XSalsa 27import qualified Crypto.Cipher.XSalsa as XSalsa
@@ -94,6 +95,7 @@ import qualified Network.Tox.Onion.Handlers as Onion
94import Network.Tox.Crypto.Transport (NetCrypto) 95import Network.Tox.Crypto.Transport (NetCrypto)
95import Text.XXD 96import Text.XXD
96import OnionRouter 97import OnionRouter
98import Data.Word64Map (fitsInInt)
97 99
98newCrypto :: IO TransportCrypto 100newCrypto :: IO TransportCrypto
99newCrypto = do 101newCrypto = do
@@ -158,7 +160,7 @@ newClient :: (DRG g, Show addr, Show meth) =>
158 -> (x -> MessageClass String meth DHT.TransactionId) 160 -> (x -> MessageClass String meth DHT.TransactionId)
159 -> (Maybe addr -> IO addr) 161 -> (Maybe addr -> IO addr)
160 -> (meth -> Maybe (MethodHandler String DHT.TransactionId addr x)) 162 -> (meth -> Maybe (MethodHandler String DHT.TransactionId addr x))
161 -> (forall d. TransactionMethods d DHT.TransactionId x -> TransactionMethods d DHT.TransactionId x) 163 -> (forall d. TransactionMethods d DHT.TransactionId addr x -> TransactionMethods d DHT.TransactionId addr x)
162 -> (Client String meth DHT.TransactionId addr x -> Transport String addr x -> Transport String addr x) 164 -> (Client String meth DHT.TransactionId addr x -> Transport String addr x -> Transport String addr x)
163 -> IO (Client String meth DHT.TransactionId addr x) 165 -> IO (Client String meth DHT.TransactionId addr x)
164newClient drg net classify selfAddr handlers modifytbl modifynet = do 166newClient drg net classify selfAddr handlers modifytbl modifynet = do
@@ -180,11 +182,12 @@ newClient drg net classify selfAddr handlers modifytbl modifynet = do
180 , lookupHandler = handlers -- var 182 , lookupHandler = handlers -- var
181 , tableMethods = modifytbl tbl 183 , tableMethods = modifytbl tbl
182 } 184 }
185 eprinter = printErrors stderr
183 mkclient (tbl,var) handlers = 186 mkclient (tbl,var) handlers =
184 let client = Client 187 let client = Client
185 { clientNet = addHandler (handleMessage client) $ modifynet client net 188 { clientNet = addHandler eprinter (handleMessage client) $ modifynet client net
186 , clientDispatcher = dispatch tbl var handlers -- (fmap (contramapAddr (\(ToxPath ni _) -> ni)) . handlers) 189 , clientDispatcher = dispatch tbl var handlers -- (fmap (contramapAddr (\(ToxPath ni _) -> ni)) . handlers)
187 , clientErrorReporter = (printErrors stderr) { reportTimeout = reportTimeout ignoreErrors } 190 , clientErrorReporter = eprinter { reportTimeout = reportTimeout ignoreErrors }
188 , clientPending = var 191 , clientPending = var
189 , clientAddress = selfAddr 192 , clientAddress = selfAddr
190 , clientResponseId = genNonce24 var 193 , clientResponseId = genNonce24 var
@@ -199,18 +202,22 @@ data Tox = Tox
199 , toxRouting :: DHT.Routing 202 , toxRouting :: DHT.Routing
200 , toxTokens :: TVar SessionTokens 203 , toxTokens :: TVar SessionTokens
201 , toxAnnouncedKeys :: TVar Onion.AnnouncedKeys 204 , toxAnnouncedKeys :: TVar Onion.AnnouncedKeys
205 , toxOnionRoutes :: OnionRouter
202 } 206 }
203 207
204addVerbosity :: Show addr => Transport err addr ByteString -> Transport err addr ByteString 208isLocalHost (SockAddrInet _ host32) = (fromBE32 host32 == 0x7f000001)
209isLocalHost _ = False
210
211addVerbosity :: Transport err SockAddr ByteString -> Transport err SockAddr ByteString
205addVerbosity tr = 212addVerbosity tr =
206 tr { awaitMessage = \kont -> awaitMessage tr $ \m -> do 213 tr { awaitMessage = \kont -> awaitMessage tr $ \m -> do
207 forM_ m $ mapM_ $ \(msg,addr) -> do 214 forM_ m $ mapM_ $ \(msg,addr) -> do
208 when (not (B.null msg || elem (B.head msg) [0,1,2,4])) $ do 215 when (isLocalHost addr || not (B.null msg || elem (B.head msg) [0,1,2,4,0x81,0x82,0x8c,0x8d])) $ do
209 mapM_ (\x -> hPutStrLn stderr ( (show addr) ++ " --> " ++ x)) 216 mapM_ (\x -> hPutStrLn stderr ( (show addr) ++ " --> " ++ x))
210 $ xxd 0 msg 217 $ xxd 0 msg
211 kont m 218 kont m
212 , sendMessage = \addr msg -> do 219 , sendMessage = \addr msg -> do
213 when (not (B.null msg || elem (B.head msg) [0,1,2,4])) $ do 220 when (isLocalHost addr || not (B.null msg || elem (B.head msg) [0,1,2,4,0x81,0x82,0x8c,0x8d])) $ do
214 mapM_ (\x -> hPutStrLn stderr ( (show addr) ++ " <-- " ++ x)) 221 mapM_ (\x -> hPutStrLn stderr ( (show addr) ++ " <-- " ++ x))
215 $ xxd 0 msg 222 $ xxd 0 msg
216 sendMessage tr addr msg 223 sendMessage tr addr msg
@@ -226,13 +233,15 @@ newTox keydb addr = do
226 crypto <- newCrypto 233 crypto <- newCrypto
227 drg <- drgNew 234 drg <- drgNew
228 let lookupClose _ = return Nothing 235 let lookupClose _ = return Nothing
229 routing <- DHT.newRouting addr crypto updateIP updateIP
230
231 (dhtcrypt,onioncrypt,cryptonet) <- toxTransport crypto (DHT.orouter routing) lookupClose udp
232 236
237 routing <- DHT.newRouting addr crypto updateIP updateIP
238 orouter <- newOnionRouter
239 (dhtcrypt,onioncrypt,cryptonet) <- toxTransport crypto orouter lookupClose udp
233 let dhtnet0 = layerTransport (DHT.decrypt crypto) (DHT.encrypt crypto) dhtcrypt 240 let dhtnet0 = layerTransport (DHT.decrypt crypto) (DHT.encrypt crypto) dhtcrypt
234 dhtclient <- newClient drg dhtnet0 DHT.classify (myAddr routing) (DHT.handlers routing) id 241 dhtclient <- newClient drg dhtnet0 DHT.classify (myAddr routing) (DHT.handlers routing) id
235 $ \client net -> onInbound (DHT.updateRouting client routing) net 242 $ \client net -> onInbound (DHT.updateRouting client routing orouter) net
243
244 orouter <- forkRouteBuilder orouter $ \nid ni -> maybe [] (\(_,ns,_)->ns) <$> DHT.getNodes dhtclient nid ni
236 245
237 toks <- do 246 toks <- do
238 nil <- nullSessionTokens 247 nil <- nullSessionTokens
@@ -240,13 +249,14 @@ newTox keydb addr = do
240 oniondrg <- drgNew 249 oniondrg <- drgNew
241 let onionnet = layerTransport (Onion.decrypt crypto) (Onion.encrypt crypto) onioncrypt 250 let onionnet = layerTransport (Onion.decrypt crypto) (Onion.encrypt crypto) onioncrypt
242 onionclient <- newClient oniondrg onionnet Onion.classify 251 onionclient <- newClient oniondrg onionnet Onion.classify
243 (const $ return 252 (const $ atomically
244 $ either (const $ error "bad sockaddr") 253 $ flip Onion.OnionDestination Nothing
245 (flip Onion.OnionDestination Nothing) 254 . R.thisNode
246 $ nodeInfo zeroID addr) 255 <$> readTVar (DHT.routing4 routing))
247 (Onion.handlers onionnet routing toks keydb) 256 (Onion.handlers onionnet routing toks keydb)
248 (hookQueries (DHT.orouter routing) DHT.transactionKey) 257 (hookQueries orouter DHT.transactionKey)
249 (const id) 258 (const id)
259
250 return Tox 260 return Tox
251 { toxDHT = dhtclient 261 { toxDHT = dhtclient
252 , toxOnion = onionclient 262 , toxOnion = onionclient
@@ -254,8 +264,12 @@ newTox keydb addr = do
254 , toxRouting = routing 264 , toxRouting = routing
255 , toxTokens = toks 265 , toxTokens = toks
256 , toxAnnouncedKeys = keydb 266 , toxAnnouncedKeys = keydb
267 , toxOnionRoutes = orouter
257 } 268 }
258 269
270onionTimeout :: Tox -> DHT.TransactionId -> Onion.OnionDestination RouteId -> STM (Onion.OnionDestination RouteId, Int)
271onionTimeout Tox { toxOnionRoutes = or } (DHT.TransactionId n8 _) od = lookupTimeout or n8 od
272
259forkTox :: Tox -> IO (IO ()) 273forkTox :: Tox -> IO (IO ())
260forkTox tox = do 274forkTox tox = do
261 _ <- forkListener "toxCrypto" (toxCrypto tox) 275 _ <- forkListener "toxCrypto" (toxCrypto tox)
diff --git a/src/Network/Tox/DHT/Handlers.hs b/src/Network/Tox/DHT/Handlers.hs
index c9adc860..a3f13ac7 100644
--- a/src/Network/Tox/DHT/Handlers.hs
+++ b/src/Network/Tox/DHT/Handlers.hs
@@ -105,7 +105,6 @@ data Routing = Routing
105 , sched6 :: !( TVar (Int.PSQ POSIXTime) ) 105 , sched6 :: !( TVar (Int.PSQ POSIXTime) )
106 , routing6 :: !( TVar (R.BucketList NodeInfo) ) 106 , routing6 :: !( TVar (R.BucketList NodeInfo) )
107 , committee6 :: TriadCommittee NodeId SockAddr 107 , committee6 :: TriadCommittee NodeId SockAddr
108 , orouter :: OnionRouter
109 } 108 }
110 109
111newRouting :: SockAddr -> TransportCrypto 110newRouting :: SockAddr -> TransportCrypto
@@ -124,8 +123,9 @@ newRouting addr crypto update4 update6 = do
124 tentative_info6 <- 123 tentative_info6 <-
125 maybe (tentative_info { nodeIP = tentative_ip6 }) 124 maybe (tentative_info { nodeIP = tentative_ip6 })
126 (\ip6 -> tentative_info { nodeIP = IPv6 ip6 }) 125 (\ip6 -> tentative_info { nodeIP = IPv6 ip6 })
127 <$> global6 126 <$> case addr of
128 orouter <- newOnionRouter 127 SockAddrInet {} -> return Nothing
128 _ -> global6
129 atomically $ do 129 atomically $ do
130 let nobkts = R.defaultBucketCount :: Int 130 let nobkts = R.defaultBucketCount :: Int
131 tbl4 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info4 nobkts 131 tbl4 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info4 nobkts
@@ -134,7 +134,7 @@ newRouting addr crypto update4 update6 = do
134 committee6 <- newTriadCommittee (update6 tbl6) -- updateIPVote tbl6 addr6 134 committee6 <- newTriadCommittee (update6 tbl6) -- updateIPVote tbl6 addr6
135 sched4 <- newTVar Int.empty 135 sched4 <- newTVar Int.empty
136 sched6 <- newTVar Int.empty 136 sched6 <- newTVar Int.empty
137 return $ Routing tentative_info sched4 tbl4 committee4 sched6 tbl6 committee6 orouter 137 return $ Routing tentative_info sched4 tbl4 committee4 sched6 tbl6 committee6
138 138
139 139
140-- TODO: This should cover more cases 140-- TODO: This should cover more cases
@@ -200,7 +200,7 @@ serializer :: PacketKind
200 -> (Message -> Maybe (Assym (Nonce8,pong))) 200 -> (Message -> Maybe (Assym (Nonce8,pong)))
201 -> MethodSerializer TransactionId NodeInfo Message PacketKind ping (Maybe pong) 201 -> MethodSerializer TransactionId NodeInfo Message PacketKind ping (Maybe pong)
202serializer pktkind mkping mkpong = MethodSerializer 202serializer pktkind mkping mkpong = MethodSerializer
203 { methodTimeout = 5 203 { methodTimeout = \tid addr -> return (addr, 5000000)
204 , method = pktkind 204 , method = pktkind
205 -- wrapQuery :: tid -> addr -> addr -> qry -> x 205 -- wrapQuery :: tid -> addr -> addr -> qry -> x
206 , wrapQuery = \tid src dst ping -> mkping $ wrapAssym tid src dst (, ping) 206 , wrapQuery = \tid src dst ping -> mkping $ wrapAssym tid src dst (, ping)
@@ -232,20 +232,20 @@ unwrapNodes (SendNodes ns) = (ns,ns,())
232 232
233getNodes :: Client -> NodeId -> NodeInfo -> IO (Maybe ([NodeInfo],[NodeInfo],())) 233getNodes :: Client -> NodeId -> NodeInfo -> IO (Maybe ([NodeInfo],[NodeInfo],()))
234getNodes client nid addr = do 234getNodes client nid addr = do
235 hPutStrLn stderr $ show addr ++ " <-- getnodes " ++ show nid 235 -- hPutStrLn stderr $ show addr ++ " <-- getnodes " ++ show nid
236 reply <- QR.sendQuery client (serializer GetNodesType DHTGetNodes unsendNodes) (GetNodes nid) addr 236 reply <- QR.sendQuery client (serializer GetNodesType DHTGetNodes unsendNodes) (GetNodes nid) addr
237 hPutStrLn stderr $ show addr ++ " -sendnodes-> " ++ show reply 237 -- hPutStrLn stderr $ show addr ++ " -sendnodes-> " ++ show reply
238 return $ fmap unwrapNodes $ join reply 238 return $ fmap unwrapNodes $ join reply
239 239
240updateRouting :: Client -> Routing -> NodeInfo -> Message -> IO () 240updateRouting :: Client -> Routing -> OnionRouter -> NodeInfo -> Message -> IO ()
241updateRouting client routing naddr msg = do 241updateRouting client routing orouter naddr msg = do
242 let typ = fst $ dhtMessageType $ fst $ DHTTransport.encrypt (error "updateRouting") msg naddr 242 let typ = fst $ dhtMessageType $ fst $ DHTTransport.encrypt (error "updateRouting") msg naddr
243 tid = mapMessage (\n24 (n8,_) -> TransactionId n8 n24) msg 243 tid = mapMessage (\n24 (n8,_) -> TransactionId n8 n24) msg
244 hPutStrLn stderr $ "updateRouting "++show (typ,tid) 244 -- hPutStrLn stderr $ "updateRouting "++show (typ,tid)
245 -- TODO: check msg type 245 -- TODO: check msg type
246 case prefer4or6 naddr Nothing of 246 case prefer4or6 naddr Nothing of
247 Want_IP4 -> updateTable client naddr (orouter routing) (routing4 routing) (committee4 routing) (sched4 routing) 247 Want_IP4 -> updateTable client naddr orouter (routing4 routing) (committee4 routing) (sched4 routing)
248 Want_IP6 -> updateTable client naddr (orouter routing) (routing6 routing) (committee6 routing) (sched6 routing) 248 Want_IP6 -> updateTable client naddr orouter (routing6 routing) (committee6 routing) (sched6 routing)
249 249
250updateTable :: Client -> NodeInfo -> OnionRouter -> TVar (R.BucketList NodeInfo) -> TriadCommittee NodeId SockAddr -> TVar (Int.PSQ POSIXTime) -> IO () 250updateTable :: Client -> NodeInfo -> OnionRouter -> TVar (R.BucketList NodeInfo) -> TriadCommittee NodeId SockAddr -> TVar (Int.PSQ POSIXTime) -> IO ()
251updateTable client naddr orouter tbl committee sched = do 251updateTable client naddr orouter tbl committee sched = do
@@ -262,7 +262,7 @@ toxKademlia client committee orouter var sched
262 { tblTransition = \tr -> do 262 { tblTransition = \tr -> do
263 io1 <- transitionCommittee committee tr 263 io1 <- transitionCommittee committee tr
264 io2 <- touchBucket toxSpace (15*60) var sched tr 264 io2 <- touchBucket toxSpace (15*60) var sched tr
265 hookBucketList orouter tr 265 hookBucketList toxSpace var orouter tr
266 return $ do 266 return $ do
267 io1 >> io2 267 io1 >> io2
268 {- 268 {-
diff --git a/src/Network/Tox/NodeId.hs b/src/Network/Tox/NodeId.hs
index 959d689c..d0c57416 100644
--- a/src/Network/Tox/NodeId.hs
+++ b/src/Network/Tox/NodeId.hs
@@ -223,7 +223,10 @@ instance Sized NodeInfo where
223instance S.Serialize NodeInfo where 223instance S.Serialize NodeInfo where
224 get = do 224 get = do
225 addrfam <- S.get :: S.Get Word8 225 addrfam <- S.get :: S.Get Word8
226 ip <- getIP addrfam 226 let fallback = do -- FIXME: Handle unrecognized address families.
227 IPv6 <$> S.get
228 return $ IPv6 (read "::" :: IPv6)
229 ip <- getIP addrfam <|> fallback
227 port <- S.get :: S.Get PortNumber 230 port <- S.get :: S.Get PortNumber
228 nid <- S.get 231 nid <- S.get
229 return $ NodeInfo nid ip port 232 return $ NodeInfo nid ip port
diff --git a/src/Network/Tox/Onion/Handlers.hs b/src/Network/Tox/Onion/Handlers.hs
index 08f5cabd..91dd843e 100644
--- a/src/Network/Tox/Onion/Handlers.hs
+++ b/src/Network/Tox/Onion/Handlers.hs
@@ -1,6 +1,8 @@
1{-# LANGUAGE PatternSynonyms #-} 1{-# LANGUAGE LambdaCase #-}
2{-# LANGUAGE PatternSynonyms #-}
2module Network.Tox.Onion.Handlers where 3module Network.Tox.Onion.Handlers where
3 4
5import Network.Kademlia.Search
4import Network.Tox.DHT.Transport 6import Network.Tox.DHT.Transport
5import Network.Tox.DHT.Handlers hiding (Message,Client) 7import Network.Tox.DHT.Handlers hiding (Message,Client)
6import Network.Tox.Onion.Transport 8import Network.Tox.Onion.Transport
@@ -11,9 +13,11 @@ import qualified Data.Wrapper.PSQ as PSQ
11 ;import Data.Wrapper.PSQ (PSQ) 13 ;import Data.Wrapper.PSQ (PSQ)
12import Crypto.Error.Types (CryptoFailable (..), 14import Crypto.Error.Types (CryptoFailable (..),
13 throwCryptoError) 15 throwCryptoError)
16import Control.Arrow
14 17
15import System.IO 18import System.IO
16import qualified Data.ByteArray as BA 19import qualified Data.ByteArray as BA
20import Data.Function
17import Data.Serialize as S 21import Data.Serialize as S
18import qualified Data.Wrapper.PSQInt as Int 22import qualified Data.Wrapper.PSQInt as Int
19import Network.Kademlia 23import Network.Kademlia
@@ -59,23 +63,27 @@ classify msg = go msg
59-- The reason for this 20 second timeout in toxcore is that it gives a reasonable 63-- The reason for this 20 second timeout in toxcore is that it gives a reasonable
60-- time (20 to 40 seconds) for a peer to announce himself while taking in count 64-- time (20 to 40 seconds) for a peer to announce himself while taking in count
61-- all the possible delays with some extra seconds. 65-- all the possible delays with some extra seconds.
66-- dhtd: src/Network/Tox/Onion/Handlers.hs:(67,1)-(101,23): Non-exhaustive patterns in function announceH
62announceH :: Routing -> TVar SessionTokens -> TVar AnnouncedKeys -> OnionDestination r -> AnnounceRequest -> IO AnnounceResponse 67announceH :: Routing -> TVar SessionTokens -> TVar AnnouncedKeys -> OnionDestination r -> AnnounceRequest -> IO AnnounceResponse
63announceH routing toks keydb (OnionToOwner naddr retpath) req = do 68announceH routing toks keydb oaddr req = do
64 case () of 69 case () of
65 _ | announcePingId req == zeros32 70 _ | announcePingId req == zeros32
66 -> go False 71 -> go False
67 72
68 _ -> let Nonce32 bs = announcePingId req 73 _ -> let Nonce32 bs = announcePingId req
69 tok = fromPaddedByteString 32 bs 74 tok = fromPaddedByteString 32 bs
70 in checkToken toks naddr tok >>= go 75 in checkToken toks (onionNodeInfo oaddr) tok >>= go
71 `catch` (\(SomeException e) -> hPutStrLn stderr ("announceH Exception! "++show e) >> throw e) 76 `catch` (\(SomeException e) -> hPutStrLn stderr ("announceH Exception! "++show e) >> throw e)
72 where 77 where
73 go withTok = do 78 go withTok = do
79 let naddr = onionNodeInfo oaddr
74 ns <- getNodesH routing naddr (GetNodes (announceSeeking req)) 80 ns <- getNodesH routing naddr (GetNodes (announceSeeking req))
75 tm <- getPOSIXTime 81 tm <- getPOSIXTime
76 let storing = (nodeId naddr == announceSeeking req) 82 let storing = case oaddr of
83 OnionToOwner _ pth -> guard (nodeId naddr == announceSeeking req) >> Just pth
84 _ -> Nothing
77 record <- atomically $ do 85 record <- atomically $ do
78 when (withTok && storing) $ do 86 forM_ storing $ \retpath -> when withTok $ do
79 let toxpath = AnnouncedRoute naddr{ nodeId = announceKey req } retpath 87 let toxpath = AnnouncedRoute naddr{ nodeId = announceKey req } retpath
80 -- Note: The following distance calculation assumes that 88 -- Note: The following distance calculation assumes that
81 -- our nodeid doesn't change and is the same for both 89 -- our nodeid doesn't change and is the same for both
@@ -85,12 +93,12 @@ announceH routing toks keydb (OnionToOwner naddr retpath) req = do
85 modifyTVar' keydb (insertKey tm (announceSeeking req) toxpath d) 93 modifyTVar' keydb (insertKey tm (announceSeeking req) toxpath d)
86 ks <- readTVar keydb 94 ks <- readTVar keydb
87 return $ snd . snd <$> MinMaxPSQ.lookup' (announceSeeking req) (keyAssoc ks) 95 return $ snd . snd <$> MinMaxPSQ.lookup' (announceSeeking req) (keyAssoc ks)
88 newtok <- if storing 96 newtok <- maybe (return $ zeros32)
89 then Nonce32 . toPaddedByteString 32 <$> grantToken toks naddr 97 (const $ Nonce32 . toPaddedByteString 32 <$> grantToken toks naddr)
90 else return $ zeros32 98 storing
91 let k = case record of 99 let k = case record of
92 Nothing -> NotStored newtok 100 Nothing -> NotStored newtok
93 Just _ | storing -> Acknowledged newtok 101 Just _ | isJust storing -> Acknowledged newtok
94 Just (AnnouncedRoute ni _) -> SendBackKey $ id2key (nodeId ni) 102 Just (AnnouncedRoute ni _) -> SendBackKey $ id2key (nodeId ni)
95 let response = AnnounceResponse k ns 103 let response = AnnounceResponse k ns
96 hPutStrLn stderr $ unwords ["Announce:", show req, "-reply->", show response] 104 hPutStrLn stderr $ unwords ["Announce:", show req, "-reply->", show response]
@@ -151,3 +159,58 @@ handlers net routing toks keydb AnnounceType
151 $ announceH routing toks keydb 159 $ announceH routing toks keydb
152handlers net _ _ keydb _ = Just $ NoReply Right $ dataToRouteH keydb net 160handlers net _ _ keydb _ = Just $ NoReply Right $ dataToRouteH keydb net
153 161
162toxidSearch :: (TransactionId -> OnionDestination r -> STM (OnionDestination r, Int))
163 -> Client r
164 -> Search NodeId (IP, PortNumber) (Maybe Nonce32) NodeInfo PublicKey
165toxidSearch getTimeout client = Search
166 { searchSpace = toxSpace
167 , searchNodeAddress = nodeIP &&& nodePort
168 , searchQuery = announce getTimeout client
169 }
170
171announceSerializer :: (TransactionId -> OnionDestination r -> STM (OnionDestination r, Int))
172 -> MethodSerializer
173 TransactionId
174 (OnionDestination r)
175 (OnionMessage Identity)
176 PacketKind
177 AnnounceRequest
178 (Maybe AnnounceResponse)
179announceSerializer getTimeout = MethodSerializer
180 { methodTimeout = getTimeout
181 , method = AnnounceType
182 , wrapQuery = \(TransactionId n8 n24) src dst req ->
183 -- :: tid -> addr -> addr -> a -> OnionMessage Identity
184 OnionAnnounce $ Assym
185 { -- The public key is our real long term public key if we want to
186 -- announce ourselves, a temporary one if we are searching for
187 -- friends.
188 senderKey = fromJust $ onionKey src -- TODO: FIXME: this should be a temporary alias key
189 , assymNonce = n24
190 , assymData = Identity (req, n8)
191 }
192 , unwrapResponse = \case -- :: OnionMessage Identity -> b
193 OnionAnnounceResponse _ _ resp -> Just $ runIdentity resp
194 _ -> Nothing
195 }
196
197unwrapAnnounceResponse :: AnnounceResponse -> ([NodeInfo], [PublicKey], Maybe Nonce32)
198unwrapAnnounceResponse (AnnounceResponse is_stored (SendNodes ns))
199 = case is_stored of
200 NotStored n32 -> (ns, [], Just n32)
201 SendBackKey k -> (ns, [k], Nothing)
202 Acknowledged n32 -> (ns, [], Just n32)
203
204announce :: (TransactionId -> OnionDestination r -> STM (OnionDestination r, Int))
205 -> Client r
206 -> NodeId
207 -> NodeInfo
208 -> IO (Maybe ([NodeInfo],[PublicKey],Maybe Nonce32))
209announce getTimeout client nid ni =
210 -- Four tries and then we tap out.
211 flip fix 4 $ \loop n -> do
212 let oaddr = OnionDestination ni Nothing
213 mb <- QR.sendQuery client (announceSerializer getTimeout) (AnnounceRequest zeros32 nid zeroID) oaddr
214 maybe (if n>0 then loop $! n - 1 else return Nothing)
215 (return . Just . unwrapAnnounceResponse)
216 $ join mb
diff --git a/src/Network/Tox/Onion/Transport.hs b/src/Network/Tox/Onion/Transport.hs
index a3c1950f..b5ac748a 100644
--- a/src/Network/Tox/Onion/Transport.hs
+++ b/src/Network/Tox/Onion/Transport.hs
@@ -35,6 +35,8 @@ module Network.Tox.Onion.Transport
35 , peelSymmetric 35 , peelSymmetric
36 , OnionRoute(..) 36 , OnionRoute(..)
37 , N3 37 , N3
38 , onionKey
39 , onionNodeInfo
38 ) where 40 ) where
39 41
40import Network.Address (fromSockAddr,toSockAddr,setPort,either4or6,sockAddrPort) 42import Network.Address (fromSockAddr,toSockAddr,setPort,either4or6,sockAddrPort)
@@ -42,10 +44,11 @@ import Network.QueryResponse
42import Crypto.Tox hiding (encrypt,decrypt) 44import Crypto.Tox hiding (encrypt,decrypt)
43import Network.Tox.NodeId 45import Network.Tox.NodeId
44import qualified Crypto.Tox as ToxCrypto 46import qualified Crypto.Tox as ToxCrypto
45import Network.Tox.DHT.Transport (NodeInfo(..),NodeId(..),SendNodes,nodeInfo,DHTPublicKey,asymNodeInfo) 47import Network.Tox.DHT.Transport (NodeInfo(..),NodeId(..),SendNodes(..),nodeInfo,DHTPublicKey,asymNodeInfo)
46 48
47import Debug.Trace 49import Debug.Trace
48import Control.Arrow 50import Control.Arrow
51import Control.Applicative
49import Control.Concurrent.STM 52import Control.Concurrent.STM
50import Control.Monad 53import Control.Monad
51import qualified Data.ByteString as B 54import qualified Data.ByteString as B
@@ -88,14 +91,23 @@ deriving instance ( Show (f (AnnounceRequest, Nonce8))
88 , Show (f DataToRoute) 91 , Show (f DataToRoute)
89 ) => Show (OnionMessage f) 92 ) => Show (OnionMessage f)
90 93
94msgNonce :: OnionMessage f -> Nonce24
95msgNonce (OnionAnnounce a) = assymNonce a
96msgNonce (OnionAnnounceResponse _ n24 _) = n24
97msgNonce (OnionToRoute _ a) = assymNonce a
98msgNonce (OnionToRouteResponse a) = assymNonce a
99
91data OnionDestination r 100data OnionDestination r
92 = OnionToOwner NodeInfo (ReturnPath N3) -- ^ Somebody else's path to us. 101 = OnionToOwner NodeInfo (ReturnPath N3) -- ^ Somebody else's path to us.
93 | OnionDestination NodeInfo (Maybe r) -- ^ Our own onion-path. 102 | OnionDestination NodeInfo (Maybe r) -- ^ Our own onion-path.
94 deriving Show 103 deriving Show
95 104
105onionNodeInfo :: OnionDestination r -> NodeInfo
106onionNodeInfo (OnionToOwner ni _) = ni
107onionNodeInfo (OnionDestination ni _) = ni
108
96onionKey :: OnionDestination r -> Maybe PublicKey 109onionKey :: OnionDestination r -> Maybe PublicKey
97onionKey (OnionToOwner ni _) = Just $ id2key (nodeId ni) 110onionKey od = Just $ id2key . nodeId $ onionNodeInfo od
98onionKey (OnionDestination ni _) = Just $ id2key (nodeId ni)
99 111
100instance Sized (OnionMessage Encrypted) where 112instance Sized (OnionMessage Encrypted) where
101 size = VarSize $ \case 113 size = VarSize $ \case
@@ -176,11 +188,19 @@ encodeOnionAddr :: (NodeInfo -> r -> IO (Maybe OnionRoute))
176encodeOnionAddr _ (msg,OnionToOwner ni p) = 188encodeOnionAddr _ (msg,OnionToOwner ni p) =
177 return $ Just ( runPut $ putResponse (OnionResponse p msg) 189 return $ Just ( runPut $ putResponse (OnionResponse p msg)
178 , nodeAddr ni ) 190 , nodeAddr ni )
179encodeOnionAddr _ (msg,OnionDestination _ Nothing ) = return Nothing 191encodeOnionAddr _ (msg,OnionDestination _ Nothing ) = do
192 hPutStrLn stderr $ "ONION encode missing routeid"
193 return Nothing
180encodeOnionAddr getRoute (msg,OnionDestination ni (Just rid)) = do 194encodeOnionAddr getRoute (msg,OnionDestination ni (Just rid)) = do
181 let go route = do 195 let go route0 = do
182 return (runPut $ putRequest $ wrapForRoute msg ni route, nodeAddr ni) 196 let route = route0 { routeNonce = msgNonce msg } -- TODO: This necessary?
183 getRoute ni rid >>= mapM go 197 return ( runPut $ putRequest $ wrapForRoute msg ni route
198 , nodeAddr $ routeNodeA route)
199 mapM' f x = do
200 hPutStrLn stderr $ "ONION encode sending to " ++ show ni
201 hPutStrLn stderr $ "ONION encode getRoute -> " ++ show (mapM (\y -> map ($ y) [routeNodeA,routeNodeB,routeNodeC]) x)
202 mapM f x
203 getRoute ni rid >>= mapM' go
184 204
185 205
186forwardOnions :: TransportCrypto -> UDPTransport -> UDPTransport 206forwardOnions :: TransportCrypto -> UDPTransport -> UDPTransport
@@ -239,16 +259,19 @@ deriving instance ( Show (Forwarding (ThreeMinus n) (OnionMessage Encrypted))
239instance ( Serialize (Forwarding (ThreeMinus n) (OnionMessage Encrypted)) 259instance ( Serialize (Forwarding (ThreeMinus n) (OnionMessage Encrypted))
240 , Sized (ReturnPath n) 260 , Sized (ReturnPath n)
241 , Serialize (ReturnPath n) 261 , Serialize (ReturnPath n)
262 , Typeable n
242 ) => Serialize (OnionRequest n) where 263 ) => Serialize (OnionRequest n) where
243 get = do 264 get = do
244 -- TODO share code with 'getOnionRequest' 265 -- TODO share code with 'getOnionRequest'
245 n24 <- get 266 n24 <- case eqT :: Maybe (n :~: N3) of
267 Just Refl -> return $ Nonce24 zeros24
268 Nothing -> get
246 cnt <- remaining 269 cnt <- remaining
247 let fwdsize = case size :: Size (ReturnPath n) of ConstSize n -> cnt - n 270 let fwdsize = case size :: Size (ReturnPath n) of ConstSize n -> cnt - n
248 fwd <- isolate fwdsize get 271 fwd <- isolate fwdsize get
249 rpath <- get 272 rpath <- get
250 return $ OnionRequest n24 fwd rpath 273 return $ OnionRequest n24 fwd rpath
251 put (OnionRequest n f p) = put n >> put f >> put p 274 put (OnionRequest n f p) = maybe (put n) (\Refl -> return ()) (eqT :: Maybe (n :~: N3)) >> put f >> put p
252 275
253-- getRequest :: _ 276-- getRequest :: _
254-- getRequest = OnionRequest <$> get <*> get <*> get 277-- getRequest = OnionRequest <$> get <*> get <*> get
@@ -402,6 +425,7 @@ handleOnionRequest :: forall a proxy n.
402 ( LessThanThree n 425 ( LessThanThree n
403 , KnownPeanoNat n 426 , KnownPeanoNat n
404 , Sized (ReturnPath n) 427 , Sized (ReturnPath n)
428 , Typeable n
405 ) => proxy n -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionRequest n -> IO a 429 ) => proxy n -> TransportCrypto -> SockAddr -> UDPTransport -> IO a -> OnionRequest n -> IO a
406handleOnionRequest proxy crypto saddr udp kont (OnionRequest nonce msg rpath) = do 430handleOnionRequest proxy crypto saddr udp kont (OnionRequest nonce msg rpath) = do
407 let n = peanoVal rpath 431 let n = peanoVal rpath
@@ -414,7 +438,7 @@ handleOnionRequest proxy crypto saddr udp kont (OnionRequest nonce msg rpath) =
414 hPutStrLn stderr $ unwords [ "peelOnion:", show n, either show show (either4or6 saddr), e] 438 hPutStrLn stderr $ unwords [ "peelOnion:", show n, either show show (either4or6 saddr), e]
415 kont 439 kont
416 Right (Addressed dst msg') -> do 440 Right (Addressed dst msg') -> do
417 hPutStrLn stderr $ unwords [ "peelOnion:", show n, either show show (either4or6 saddr), "SUCCESS"] 441 hPutStrLn stderr $ unwords [ "peelOnion:", show n, either show show (either4or6 saddr), "-->", either show show (either4or6 dst), "SUCCESS"]
418 sendMessage udp dst (runPut $ putRequest $ OnionRequest nonce msg' $ wrapSymmetric sym snonce saddr rpath) 442 sendMessage udp dst (runPut $ putRequest $ OnionRequest nonce msg' $ wrapSymmetric sym snonce saddr rpath)
419 kont 443 kont
420 444
@@ -472,9 +496,13 @@ getOnionRequest = do
472 path <- get 496 path <- get
473 return (a,path) 497 return (a,path)
474 498
475putRequest :: (KnownPeanoNat n, Serialize (OnionRequest n)) => OnionRequest n -> Put 499putRequest :: ( KnownPeanoNat n
500 , Serialize (OnionRequest n)
501 , Typeable n
502 ) => OnionRequest n -> Put
476putRequest req = do 503putRequest req = do
477 putWord8 $ 0x80 + fromIntegral (peanoVal req) 504 let tag = 0x80 + fromIntegral (peanoVal req)
505 when (tag <= 0x82) (putWord8 tag)
478 put req 506 put req
479 507
480putResponse :: (KnownPeanoNat n, Serialize (OnionResponse n)) => OnionResponse n -> Put 508putResponse :: (KnownPeanoNat n, Serialize (OnionResponse n)) => OnionResponse n -> Put
@@ -513,9 +541,14 @@ data AnnounceResponse = AnnounceResponse
513instance Sized AnnounceResponse where 541instance Sized AnnounceResponse where
514 size = contramap is_stored size <> contramap announceNodes size 542 size = contramap is_stored size <> contramap announceNodes size
515 543
544getNodeList :: S.Get [NodeInfo]
545getNodeList = do
546 n <- S.get
547 (:) n <$> (getNodeList <|> pure [])
548
516instance S.Serialize AnnounceResponse where 549instance S.Serialize AnnounceResponse where
517 get = AnnounceResponse <$> S.get <*> S.get 550 get = AnnounceResponse <$> S.get <*> (SendNodes <$> getNodeList)
518 put (AnnounceResponse st ns) = S.put st >> S.put ns 551 put (AnnounceResponse st (SendNodes ns)) = S.put st >> mapM_ S.put ns
519 552
520data DataToRoute = DataToRoute 553data DataToRoute = DataToRoute
521 { dataFromKey :: PublicKey -- Real public key of sender 554 { dataFromKey :: PublicKey -- Real public key of sender