diff options
author | joe <joe@jerkface.net> | 2017-08-05 03:43:42 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-08-05 03:43:42 -0400 |
commit | 48f9c47ed7ed496ae0a1453fa107fae2f386f07f (patch) | |
tree | 43956c23d1269c2e0102b23d4ca98e6365e59f61 | |
parent | 036bfce939c38f7fc98b96e1a9bf11135929cb5d (diff) |
WIP changing Tox packets.
-rw-r--r-- | Tox.hs | 288 |
1 files changed, 201 insertions, 87 deletions
@@ -70,10 +70,17 @@ import Network.BitTorrent.DHT.Search (Search (..)) | |||
70 | import Text.Printf | 70 | import Text.Printf |
71 | import qualified Crypto.Cipher.ChaChaPoly1305 as Symmetric | 71 | import qualified Crypto.Cipher.ChaChaPoly1305 as Symmetric |
72 | import Data.Bitraversable (bisequence) | 72 | import Data.Bitraversable (bisequence) |
73 | import ToxMessage (quoted,bin2hex) | ||
74 | import qualified ToxMessage as Tox | ||
73 | 75 | ||
76 | {- | ||
74 | newtype NodeId = NodeId ByteString | 77 | newtype NodeId = NodeId ByteString |
75 | deriving (Eq,Ord,ByteArrayAccess, Bits, Hashable) | 78 | deriving (Eq,Ord,ByteArrayAccess, Bits, Hashable) |
79 | -} | ||
80 | |||
81 | type NodeId = Tox.PubKey | ||
76 | 82 | ||
83 | {- | ||
77 | instance Show NodeId where | 84 | instance Show NodeId where |
78 | show (NodeId bs) = C8.unpack $ Base16.encode bs | 85 | show (NodeId bs) = C8.unpack $ Base16.encode bs |
79 | 86 | ||
@@ -90,9 +97,10 @@ instance Read NodeId where | |||
90 | , B.length bs == 32 | 97 | , B.length bs == 32 |
91 | = [ (NodeId bs, drop 64 str) ] | 98 | = [ (NodeId bs, drop 64 str) ] |
92 | | otherwise = [] | 99 | | otherwise = [] |
100 | -} | ||
93 | 101 | ||
94 | zeroID :: NodeId | 102 | zeroID :: NodeId |
95 | zeroID = NodeId $ B.replicate 32 0 | 103 | zeroID = Tox.PubKey $ B.replicate 32 0 |
96 | 104 | ||
97 | data NodeInfo = NodeInfo | 105 | data NodeInfo = NodeInfo |
98 | { nodeId :: NodeId | 106 | { nodeId :: NodeId |
@@ -128,7 +136,7 @@ instance FromJSON NodeInfo where | |||
128 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) | 136 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) |
129 | let (bs,_) = Base16.decode (C8.pack nidstr) | 137 | let (bs,_) = Base16.decode (C8.pack nidstr) |
130 | guard (B.length bs == 32) | 138 | guard (B.length bs == 32) |
131 | return $ NodeInfo (NodeId bs) ip (fromIntegral (portnum :: Word16)) | 139 | return $ NodeInfo (Tox.PubKey bs) ip (fromIntegral (portnum :: Word16)) |
132 | 140 | ||
133 | getIP :: Word8 -> S.Get IP | 141 | getIP :: Word8 -> S.Get IP |
134 | getIP 0x02 = IPv4 <$> S.get | 142 | getIP 0x02 = IPv4 <$> S.get |
@@ -173,7 +181,7 @@ instance Read NodeInfo where | |||
173 | RP.char '@' RP.+++ RP.satisfy isSpace | 181 | RP.char '@' RP.+++ RP.satisfy isSpace |
174 | addrstr <- parseAddr | 182 | addrstr <- parseAddr |
175 | nid <- case Base16.decode $ C8.pack hexhash of | 183 | nid <- case Base16.decode $ C8.pack hexhash of |
176 | (bs,_) | B.length bs==32 -> return (NodeId bs) | 184 | (bs,_) | B.length bs==32 -> return (Tox.PubKey bs) |
177 | _ -> fail "Bad node id." | 185 | _ -> fail "Bad node id." |
178 | return (nid,addrstr) | 186 | return (nid,addrstr) |
179 | (nid,addrstr) <- ( nodeidAt RP.+++ ( (zeroID,) <$> parseAddr) ) | 187 | (nid,addrstr) <- ( nodeidAt RP.+++ ( (zeroID,) <$> parseAddr) ) |
@@ -217,40 +225,35 @@ nodeInfo nid saddr | |||
217 | 225 | ||
218 | data TransactionId = TransactionId | 226 | data TransactionId = TransactionId |
219 | { transactionKey :: Nonce8 -- ^ Used to lookup pending query. | 227 | { transactionKey :: Nonce8 -- ^ Used to lookup pending query. |
220 | , cryptoNonce :: Nonce24 -- ^ Used during the encryption layer. | 228 | , cryptoNonce :: Tox.Nonce24 -- ^ Used during the encryption layer. |
221 | } | 229 | } |
222 | 230 | ||
223 | -- https://toktok.ltd/spec#packet-kind | 231 | pattern PingType = Tox.PacketKind 0 -- 0x00 Ping Request |
224 | -- calls this "Packet Kind" | 232 | pattern PongType = Tox.PacketKind 1 -- 0x01 Ping Response |
225 | newtype Method = MessageType Word8 | 233 | pattern GetNodesType = Tox.PacketKind 2 -- 0x02 Nodes Request |
226 | deriving (Eq, Ord, S.Serialize) | 234 | pattern SendNodesType = Tox.PacketKind 4 -- 0x04 Nodes Response |
227 | |||
228 | pattern PingType = MessageType 0 -- 0x00 Ping Request | ||
229 | pattern PongType = MessageType 1 -- 0x01 Ping Response | ||
230 | pattern GetNodesType = MessageType 2 -- 0x02 Nodes Request | ||
231 | pattern SendNodesType = MessageType 4 -- 0x04 Nodes Response | ||
232 | -- 0x18 Cookie Request | 235 | -- 0x18 Cookie Request |
233 | -- 0x19 Cookie Response | 236 | -- 0x19 Cookie Response |
234 | -- 0x1a Crypto Handshake | 237 | -- 0x1a Crypto Handshake |
235 | -- 0x1b Crypto Data | 238 | -- 0x1b Crypto Data |
236 | 239 | ||
237 | -- TODO: Auth fail: | 240 | -- TODO: Auth fail: |
238 | pattern DHTRequestType = MessageType 32 -- 0x20 DHT Request | 241 | pattern DHTRequestType = Tox.PacketKind 32 -- 0x20 DHT Request |
239 | 242 | ||
240 | -- 0x21 LAN Discovery | 243 | -- 0x21 LAN Discovery |
241 | 244 | ||
242 | -- TODO: Auth fail: | 245 | -- TODO: Auth fail: |
243 | pattern OnionRequest0 = MessageType 128 -- 0x80 Onion Request 0 | 246 | pattern OnionRequest0 = Tox.PacketKind 128 -- 0x80 Onion Request 0 |
244 | pattern OnionRequest1 = MessageType 129 -- 0x81 Onion Request 1 | 247 | pattern OnionRequest1 = Tox.PacketKind 129 -- 0x81 Onion Request 1 |
245 | pattern OnionRequest2 = MessageType 130 -- 0x82 Onion Request 2 | 248 | pattern OnionRequest2 = Tox.PacketKind 130 -- 0x82 Onion Request 2 |
246 | pattern AnnounceType = MessageType 131 -- 0x83 Announce Request | 249 | pattern AnnounceType = Tox.PacketKind 131 -- 0x83 Announce Request |
247 | 250 | ||
248 | -- 0x84 Announce Response | 251 | -- 0x84 Announce Response |
249 | -- 0x85 Onion Data Request (data to route request packet) | 252 | -- 0x85 Onion Data Request (data to route request packet) |
250 | -- 0x86 Onion Data Response (data to route response packet) | 253 | -- 0x86 Onion Data Response (data to route response packet) |
251 | -- 0x8c Onion Response 3 | 254 | -- 0x8c Onion Response 3 |
252 | -- 0x8d Onion Response 2 | 255 | -- 0x8d Onion Response 2 |
253 | pattern OnionResponse1 = MessageType 142 -- 0x8e Onion Response 1 | 256 | pattern OnionResponse1 = Tox.PacketKind 142 -- 0x8e Onion Response 1 |
254 | -- 0xf0 Bootstrap Info | 257 | -- 0xf0 Bootstrap Info |
255 | 258 | ||
256 | -- TODO Fix these fails... | 259 | -- TODO Fix these fails... |
@@ -262,7 +265,7 @@ pattern OnionResponse1 = MessageType 142 -- 0x8e Onion Response 1 | |||
262 | -- MessageType 32 decipherAndAuth: auth fail | 265 | -- MessageType 32 decipherAndAuth: auth fail |
263 | 266 | ||
264 | 267 | ||
265 | instance Show Method where | 268 | instance Show Tox.PacketKind where |
266 | showsPrec d PingType = mappend "PingType" | 269 | showsPrec d PingType = mappend "PingType" |
267 | showsPrec d PongType = mappend "PongType" | 270 | showsPrec d PongType = mappend "PongType" |
268 | showsPrec d GetNodesType = mappend "GetNodesType" | 271 | showsPrec d GetNodesType = mappend "GetNodesType" |
@@ -271,10 +274,10 @@ instance Show Method where | |||
271 | showsPrec d OnionRequest0 = mappend "OnionRequest0" | 274 | showsPrec d OnionRequest0 = mappend "OnionRequest0" |
272 | showsPrec d OnionResponse1 = mappend "OnionResponse1" | 275 | showsPrec d OnionResponse1 = mappend "OnionResponse1" |
273 | showsPrec d AnnounceType = mappend "AnnounceType" | 276 | showsPrec d AnnounceType = mappend "AnnounceType" |
274 | showsPrec d (MessageType x) = mappend "MessageType " . showsPrec (d+1) x | 277 | showsPrec d (Tox.PacketKind x) = mappend "PacketKind " . showsPrec (d+1) x |
275 | 278 | ||
276 | newtype Nonce8 = Nonce8 Word64 | 279 | newtype Nonce8 = Nonce8 Word64 |
277 | deriving (Eq, Ord) | 280 | deriving (Eq, Ord, S.Serialize) |
278 | 281 | ||
279 | instance ByteArrayAccess Nonce8 where | 282 | instance ByteArrayAccess Nonce8 where |
280 | length _ = 8 | 283 | length _ = 8 |
@@ -286,43 +289,52 @@ instance ByteArrayAccess Nonce8 where | |||
286 | instance Show Nonce8 where | 289 | instance Show Nonce8 where |
287 | showsPrec d nonce = quoted (mappend $ bin2hex nonce) | 290 | showsPrec d nonce = quoted (mappend $ bin2hex nonce) |
288 | 291 | ||
289 | newtype Nonce24 = Nonce24 ByteString | 292 | {- |
293 | newtype Tox.Nonce24 = Tox.Nonce24 ByteString | ||
290 | deriving (Eq, Ord, ByteArrayAccess) | 294 | deriving (Eq, Ord, ByteArrayAccess) |
291 | 295 | ||
292 | instance Show Nonce24 where | 296 | instance show tox.nonce24 where |
293 | showsPrec d nonce = quoted (mappend $ bin2hex nonce) | 297 | showsprec d nonce = quoted (mappend $ bin2hex nonce) |
294 | |||
295 | instance S.Serialize Nonce24 where | ||
296 | get = Nonce24 <$> S.getBytes 24 | ||
297 | put (Nonce24 bs) = S.putByteString bs | ||
298 | |||
299 | quoted :: ShowS -> ShowS | ||
300 | quoted shows s = '"':shows ('"':s) | ||
301 | 298 | ||
302 | bin2hex :: ByteArrayAccess bs => bs -> String | 299 | instance S.Serialize Tox.Nonce24 where |
303 | bin2hex = C8.unpack . Base16.encode . BA.convert | 300 | get = Tox.Nonce24 <$> S.getBytes 24 |
301 | put (Tox.Nonce24 bs) = S.putByteString bs | ||
302 | -} | ||
304 | 303 | ||
305 | newtype SymmetricCiphered = SymmetricCiphered ByteString | 304 | newtype SymmetricCiphered = SymmetricCiphered ByteString |
306 | deriving (Eq,Show) | 305 | deriving (Eq,Show) |
307 | 306 | ||
307 | {- | ||
308 | data Message a = Message | 308 | data Message a = Message |
309 | { msgType :: Method | 309 | { msgType :: Method |
310 | , msgOrigin :: NodeId | 310 | , msgOrigin :: NodeId |
311 | , msgNonce :: Nonce24 -- cryptoNonce of TransactionId | 311 | , msgNonce :: Tox.Nonce24 -- cryptoNonce of TransactionId |
312 | , msgReturnPath :: Maybe SymmetricCiphered | 312 | , msgReturnPath :: Maybe (Tox.Nonce24,SymmetricCiphered) |
313 | , msgPayload :: a | 313 | , msgPayload :: a |
314 | } | 314 | } |
315 | deriving (Eq, Show, Generic, Functor, Foldable, Traversable) | 315 | deriving (Eq, Show, Generic, Functor, Foldable, Traversable) |
316 | -} | ||
317 | |||
318 | data Msg = Msg | ||
319 | { msgType :: Tox.PacketKind | ||
320 | , msgNonce :: Tox.Nonce24 | ||
321 | , msgData :: ByteString | ||
322 | , msgSendBack :: Nonce8 | ||
323 | } | ||
324 | deriving Show | ||
325 | |||
316 | 326 | ||
317 | typeHasEncryptedPayload OnionResponse1 = False | 327 | typeHasEncryptedPayload OnionResponse1 = False |
318 | typeHasEncryptedPayload _ = True | 328 | typeHasEncryptedPayload _ = True |
319 | 329 | ||
330 | {- | ||
320 | msgDHTKey Message{ msgOrigin, msgType = PingType } = Just msgOrigin | 331 | msgDHTKey Message{ msgOrigin, msgType = PingType } = Just msgOrigin |
321 | msgDHTKey Message{ msgOrigin, msgType = PongType } = Just msgOrigin | 332 | msgDHTKey Message{ msgOrigin, msgType = PongType } = Just msgOrigin |
322 | msgDHTKey Message{ msgOrigin, msgType = GetNodesType } = Just msgOrigin | 333 | msgDHTKey Message{ msgOrigin, msgType = GetNodesType } = Just msgOrigin |
323 | msgDHTKey Message{ msgOrigin, msgType = SendNodesType } = Just msgOrigin | 334 | msgDHTKey Message{ msgOrigin, msgType = SendNodesType } = Just msgOrigin |
324 | msgDHTKey Message{ msgOrigin, msgType = OnionRequest0 } = Just msgOrigin | 335 | msgDHTKey Message{ msgOrigin, msgType = OnionRequest0 } = Just msgOrigin |
325 | msgDHTKey _ = Nothing | 336 | msgDHTKey _ = Nothing |
337 | -} | ||
326 | 338 | ||
327 | data Ciphered = Ciphered { cipheredMAC :: Poly1305.Auth | 339 | data Ciphered = Ciphered { cipheredMAC :: Poly1305.Auth |
328 | , cipheredBytes :: ByteString } | 340 | , cipheredBytes :: ByteString } |
@@ -334,6 +346,7 @@ instance S.Serialize OnionPayload where | |||
334 | get = OnionPayload <$> (S.remaining >>= S.getBytes) | 346 | get = OnionPayload <$> (S.remaining >>= S.getBytes) |
335 | put (OnionPayload bs) = S.putByteString bs | 347 | put (OnionPayload bs) = S.putByteString bs |
336 | 348 | ||
349 | {- | ||
337 | getMessage :: S.Get (Message (Either OnionPayload Ciphered)) | 350 | getMessage :: S.Get (Message (Either OnionPayload Ciphered)) |
338 | getMessage = do | 351 | getMessage = do |
339 | typ <- S.get | 352 | typ <- S.get |
@@ -377,10 +390,13 @@ putMessage (Message {..}) = do | |||
377 | AnnounceType -> S.put msgNonce >> S.put msgOrigin | 390 | AnnounceType -> S.put msgNonce >> S.put msgOrigin |
378 | _ -> S.put msgOrigin >> S.put msgNonce | 391 | _ -> S.put msgOrigin >> S.put msgNonce |
379 | let putPayload = either putOnionPayload putCiphered msgPayload | 392 | let putPayload = either putOnionPayload putCiphered msgPayload |
380 | putReturnPath = forM_ msgReturnPath $ \(SymmetricCiphered bs) -> S.putByteString bs | 393 | putReturnPath = forM_ msgReturnPath |
394 | $ \(nonce,SymmetricCiphered bs) -> do S.put nonce | ||
395 | S.putByteString bs | ||
381 | case msgType of | 396 | case msgType of |
382 | OnionResponse1 -> putReturnPath >> putPayload | 397 | OnionResponse1 -> putReturnPath >> putPayload |
383 | _ -> putPayload >> putReturnPath | 398 | _ -> putPayload >> putReturnPath |
399 | -} | ||
384 | 400 | ||
385 | {- | 401 | {- |
386 | data Plain a = Plain | 402 | data Plain a = Plain |
@@ -425,7 +441,7 @@ hsalsa20 k n = a <> b | |||
425 | (b, _ ) = BA.splitAt 16 bs | 441 | (b, _ ) = BA.splitAt 16 bs |
426 | 442 | ||
427 | 443 | ||
428 | computeSharedSecret :: SecretKey -> NodeId -> Nonce24 -> (Poly1305.State, XSalsa.State) | 444 | computeSharedSecret :: SecretKey -> NodeId -> Tox.Nonce24 -> (Poly1305.State, XSalsa.State) |
429 | computeSharedSecret sk recipient nonce = (hash, crypt) | 445 | computeSharedSecret sk recipient nonce = (hash, crypt) |
430 | where | 446 | where |
431 | -- diffie helman | 447 | -- diffie helman |
@@ -440,16 +456,40 @@ computeSharedSecret sk recipient nonce = (hash, crypt) | |||
440 | Cryptonite.CryptoPassed hash = Poly1305.initialize rs | 456 | Cryptonite.CryptoPassed hash = Poly1305.initialize rs |
441 | 457 | ||
442 | 458 | ||
459 | {- | ||
443 | encryptMessage :: SecretKey -> SecretsCache -> NodeId -> Message ByteString -> Message (Either OnionPayload Ciphered) | 460 | encryptMessage :: SecretKey -> SecretsCache -> NodeId -> Message ByteString -> Message (Either OnionPayload Ciphered) |
444 | encryptMessage sk _ recipient plaintext | 461 | encryptMessage sk _ recipient plaintext |
445 | = if typeHasEncryptedPayload (msgType plaintext) | 462 | = if typeHasEncryptedPayload (msgType plaintext) |
446 | then Right . withSecret encipherAndHash sk recipient (msgNonce plaintext) <$> plaintext | 463 | then Right . withSecret encipherAndHash sk recipient (msgNonce plaintext) <$> plaintext |
447 | else Left . OnionPayload <$> plaintext | 464 | else Left . OnionPayload <$> plaintext |
465 | -} | ||
448 | 466 | ||
467 | encryptAssymetric :: SecretKey -> NodeId -> NodeId -> Msg -> (Tox.PacketKind, Tox.Assymetric) | ||
468 | encryptAssymetric sk pk recipient (Msg typ nonce plaintext sendback) | ||
469 | = ( typ | ||
470 | , Tox.Assymetric | ||
471 | { senderKey = pk | ||
472 | , sent = Tox.UnclaimedAssymetric | ||
473 | { assymetricNonce = nonce | ||
474 | , assymetricData = withSecret encipherAndHash sk recipient nonce (plaintext <> S.encode sendback) | ||
475 | } | ||
476 | } ) | ||
449 | 477 | ||
478 | {- | ||
450 | decryptMessage :: SecretKey -> SecretsCache -> Message Ciphered -> Either String (Message ByteString) | 479 | decryptMessage :: SecretKey -> SecretsCache -> Message Ciphered -> Either String (Message ByteString) |
451 | decryptMessage sk _ ciphertext | 480 | decryptMessage sk _ ciphertext |
452 | = mapM (withSecret decipherAndAuth sk (msgOrigin ciphertext) (msgNonce ciphertext)) ciphertext | 481 | = mapM (withSecret decipherAndAuth sk (msgOrigin ciphertext) (msgNonce ciphertext)) ciphertext |
482 | -} | ||
483 | |||
484 | decryptAssymetric :: SecretKey -> (Tox.PacketKind, Tox.Assymetric) -> Either String Msg | ||
485 | decryptAssymetric sk (typ,assym) | ||
486 | = f <$> withSecret decipherAndAuth sk | ||
487 | (Tox.senderKey assym) | ||
488 | nonce | ||
489 | (Tox.assymetricData . Tox.sent $ assym) | ||
490 | where | ||
491 | nonce = Tox.assymetricNonce . Tox.sent $ assym | ||
492 | f bs = uncurry (Msg typ nonce) . second (either (const (Nonce8 0)) id . S.decode) $ B.splitAt (B.length bs - 8) bs | ||
453 | 493 | ||
454 | withSecret f sk recipient nonce x = f hash crypt x | 494 | withSecret f sk recipient nonce x = f hash crypt x |
455 | where | 495 | where |
@@ -458,14 +498,14 @@ withSecret f sk recipient nonce x = f hash crypt x | |||
458 | 498 | ||
459 | -- Encrypt-then-Mac: Encrypt the cleartext, then compute the MAC on the | 499 | -- Encrypt-then-Mac: Encrypt the cleartext, then compute the MAC on the |
460 | -- ciphertext, and prepend it to the ciphertext | 500 | -- ciphertext, and prepend it to the ciphertext |
461 | encipherAndHash :: Poly1305.State -> XSalsa.State -> ByteString -> Ciphered | 501 | encipherAndHash :: Poly1305.State -> XSalsa.State -> ByteString -> Tox.ImplicitAssymetric |
462 | encipherAndHash hash crypt m = Ciphered a c | 502 | encipherAndHash hash crypt m = Tox.ImplicitAssymetric (Tox.Auth a) c |
463 | where | 503 | where |
464 | c = fst . XSalsa.combine crypt $ m | 504 | c = fst . XSalsa.combine crypt $ m |
465 | a = Poly1305.finalize . Poly1305.update hash $ c | 505 | a = Poly1305.finalize . Poly1305.update hash $ c |
466 | 506 | ||
467 | decipherAndAuth :: Poly1305.State -> XSalsa.State -> Ciphered -> Either String ByteString | 507 | decipherAndAuth :: Poly1305.State -> XSalsa.State -> Tox.ImplicitAssymetric -> Either String ByteString |
468 | decipherAndAuth hash crypt (Ciphered mac c) | 508 | decipherAndAuth hash crypt (Tox.ImplicitAssymetric (Tox.Auth mac) c) |
469 | | (a == mac) = Right m | 509 | | (a == mac) = Right m |
470 | | otherwise = Left "decipherAndAuth: auth fail" | 510 | | otherwise = Left "decipherAndAuth: auth fail" |
471 | where | 511 | where |
@@ -483,6 +523,7 @@ xxd offset bs = printf "%03x: %s" offset ds : xxd (offset + B.length | |||
483 | $ B.unpack xs | 523 | $ B.unpack xs |
484 | (xs,bs') = B.splitAt 16 bs | 524 | (xs,bs') = B.splitAt 16 bs |
485 | 525 | ||
526 | {- | ||
486 | showPayloadError ciphered naddr flow err = unlines (map (prefix ++) xs) | 527 | showPayloadError ciphered naddr flow err = unlines (map (prefix ++) xs) |
487 | where | 528 | where |
488 | xs = unwords [show (msgType ciphered), err] | 529 | xs = unwords [show (msgType ciphered), err] |
@@ -492,7 +533,6 @@ showPayloadError ciphered naddr flow err = unlines (map (prefix ++) xs) | |||
492 | 533 | ||
493 | prefix = show naddr <> flow | 534 | prefix = show naddr <> flow |
494 | 535 | ||
495 | |||
496 | showParseError bs addr err = unlines $ | 536 | showParseError bs addr err = unlines $ |
497 | concat [ either show show (either4or6 addr), " --> ", err ] | 537 | concat [ either show show (either4or6 addr), " --> ", err ] |
498 | : xxd 0 bs | 538 | : xxd 0 bs |
@@ -521,7 +561,30 @@ parsePacket sk cache bs addr = left (showParseError bs addr) $ do | |||
521 | encodePacket :: SecretKey -> SecretsCache -> Message ByteString -> NodeInfo -> (ByteString, SockAddr) | 561 | encodePacket :: SecretKey -> SecretsCache -> Message ByteString -> NodeInfo -> (ByteString, SockAddr) |
522 | encodePacket sk cache msg ni = ( S.runPut . putMessage $ encryptMessage sk cache (nodeId ni) msg | 562 | encodePacket sk cache msg ni = ( S.runPut . putMessage $ encryptMessage sk cache (nodeId ni) msg |
523 | , nodeAddr ni ) | 563 | , nodeAddr ni ) |
564 | -} | ||
565 | |||
566 | msgLayer :: SecretKey | ||
567 | -> NodeId | ||
568 | -> Transport String NodeInfo (Tox.PacketKind,Tox.Assymetric) | ||
569 | -> Transport String NodeInfo Msg | ||
570 | msgLayer sk pk = layerTransport parse serialize | ||
571 | where | ||
572 | parse x addr = fmap (,addr) $ decryptAssymetric sk x | ||
573 | serialize x addr = (encryptAssymetric sk pk (nodeId addr) x, addr) | ||
574 | |||
575 | asymLayer :: Transport String SockAddr Tox.Packet -> Transport String NodeInfo (Tox.PacketKind,Tox.Assymetric) | ||
576 | asymLayer = layerTransport parse serialize | ||
577 | where | ||
578 | parse x addr = case Tox.pktClass (Tox.pktKind x) of | ||
579 | Tox.AssymetricClass top fromp -> fmap ((Tox.pktKind x,y),) $ nodeInfo (Tox.senderKey y) addr where y = fromp x | ||
524 | 580 | ||
581 | serialize (typ,assym) addr = (x,nodeAddr addr) | ||
582 | where x = case Tox.pktClass typ of | ||
583 | Tox.AssymetricClass top _ -> top assym | ||
584 | |||
585 | toxLayer :: Transport String SockAddr ByteString -> Transport String SockAddr Tox.Packet | ||
586 | toxLayer = layerTransport (\x addr -> (,addr) <$> S.decode x) | ||
587 | (\x addr -> (S.encode x, addr)) | ||
525 | 588 | ||
526 | data Routing = Routing | 589 | data Routing = Routing |
527 | { tentativeId :: NodeInfo | 590 | { tentativeId :: NodeInfo |
@@ -533,13 +596,27 @@ data Routing = Routing | |||
533 | , committee6 :: TriadCommittee NodeId SockAddr | 596 | , committee6 :: TriadCommittee NodeId SockAddr |
534 | } | 597 | } |
535 | 598 | ||
536 | type ToxClient = Client String Method TransactionId NodeInfo (Message ByteString) | 599 | type ToxClient = Client String Tox.PacketKind TransactionId NodeInfo Msg |
600 | |||
601 | encodePayload :: S.Serialize b => Tox.PacketKind -> TransactionId -> addr -> addr -> b -> Msg | ||
602 | encodePayload typ (TransactionId nonce8 nonce24) _ _ b = Msg typ nonce24 (S.encode b) nonce8 | ||
603 | |||
604 | trimPackets :: SockAddr -> ByteString -> IO (Maybe (ByteString -> ByteString)) | ||
605 | trimPackets addr bs = do | ||
606 | hPutStrLn stderr $ "GOT " ++ show (Tox.PacketKind (B.head bs)) | ||
607 | return $ case Tox.PacketKind (B.head bs) of | ||
608 | PingType -> Just id | ||
609 | PongType -> Just id | ||
610 | SendNodesType -> Just id | ||
611 | GetNodesType -> Just id | ||
612 | _ -> Nothing | ||
537 | 613 | ||
538 | newClient :: SockAddr -> IO (ToxClient, Routing) | 614 | newClient :: SockAddr -> IO (ToxClient, Routing) |
539 | newClient addr = do | 615 | newClient addr = do |
540 | udp <- udpTransport addr | 616 | udp <- udpTransport addr |
541 | secret <- generateSecretKey | 617 | secret <- generateSecretKey |
542 | let pubkey = key2id $ toPublic secret | 618 | let pubkey = key2id $ toPublic secret |
619 | hPutStrLn stderr $ "pubkey = " ++ show pubkey | ||
543 | cache <- newEmptyCache | 620 | cache <- newEmptyCache |
544 | (symkey, drg) <- do | 621 | (symkey, drg) <- do |
545 | drg0 <- getSystemDRG | 622 | drg0 <- getSystemDRG |
@@ -587,17 +664,14 @@ newClient addr = do | |||
587 | let mapT = transactionMethods (contramapT nonceKey mapMethods) gen | 664 | let mapT = transactionMethods (contramapT nonceKey mapMethods) gen |
588 | map_var <- atomically $ newTVar (drg, mempty) | 665 | map_var <- atomically $ newTVar (drg, mempty) |
589 | return $ Left (mapT,map_var) | 666 | return $ Left (mapT,map_var) |
590 | let net = onInbound (updateRouting outgoingClient routing) | 667 | let net = addHandler (handleMessage client) |
591 | $ addVerbosity | 668 | $ addVerbosity |
592 | $ layerTransport (parsePacket secret cache) | 669 | $ msgLayer secret pubkey |
593 | (encodePacket secret cache) | 670 | $ onInbound (updateRouting client routing) |
594 | $ udp | 671 | $ asymLayer |
595 | 672 | $ toxLayer | |
596 | -- Paranoid: It's safe to define /net/ and /client/ to be mutually | 673 | $ addVerbosity2 |
597 | -- recursive since 'updateRouting' does not invoke 'awaitMessage' which | 674 | $ addHandler trimPackets udp |
598 | -- which was modified by 'onInbound'. However, I'm going to avoid the | ||
599 | -- mutual reference just to be safe. | ||
600 | outgoingClient = client { clientNet = net { awaitMessage = ($ Nothing) } } | ||
601 | 675 | ||
602 | dispatch tbl var = DispatchMethods | 676 | dispatch tbl var = DispatchMethods |
603 | { classifyInbound = classify | 677 | { classifyInbound = classify |
@@ -605,6 +679,11 @@ newClient addr = do | |||
605 | , tableMethods = tbl | 679 | , tableMethods = tbl |
606 | } | 680 | } |
607 | 681 | ||
682 | handler typ f = Just $ MethodHandler (S.decode . msgData) (encodePayload typ) f | ||
683 | |||
684 | -- (decryptAssymetric secret) (encryptAssymetric secret . cryptoNonce) f | ||
685 | |||
686 | |||
608 | -- handlers :: TVar -> Method -> Maybe Handler | 687 | -- handlers :: TVar -> Method -> Maybe Handler |
609 | handlers var PingType = handler PongType pingH | 688 | handlers var PingType = handler PongType pingH |
610 | handlers var GetNodesType = handler SendNodesType $ getNodesH routing | 689 | handlers var GetNodesType = handler SendNodesType $ getNodesH routing |
@@ -627,15 +706,15 @@ newClient addr = do | |||
627 | (g,pending) <- readTVar var | 706 | (g,pending) <- readTVar var |
628 | let (bs, g') = randomBytesGenerate 24 g | 707 | let (bs, g') = randomBytesGenerate 24 g |
629 | writeTVar var (g',pending) | 708 | writeTVar var (g',pending) |
630 | return $ TransactionId nonce8 (Nonce24 bs) | 709 | return $ TransactionId nonce8 (Tox.Nonce24 bs) |
631 | 710 | ||
632 | client = either mkclient mkclient tblvar | 711 | client = either mkclient mkclient tblvar |
633 | 712 | ||
634 | mkclient :: DRG g => | 713 | mkclient :: DRG g => |
635 | ( TransactionMethods (g,t (MVar (Message ByteString))) | 714 | ( TransactionMethods (g,t (MVar Msg)) |
636 | TransactionId | 715 | TransactionId |
637 | (Message ByteString) | 716 | Msg |
638 | , TVar (g, t (MVar (Message ByteString))) | 717 | , TVar (g, t (MVar Msg)) |
639 | ) -> ToxClient | 718 | ) -> ToxClient |
640 | mkclient (tbl,var) = Client | 719 | mkclient (tbl,var) = Client |
641 | { clientNet = net | 720 | { clientNet = net |
@@ -676,6 +755,7 @@ toxSpace = R.KademliaSpace | |||
676 | } | 755 | } |
677 | 756 | ||
678 | 757 | ||
758 | {- | ||
679 | last8 :: ByteString -> Nonce8 | 759 | last8 :: ByteString -> Nonce8 |
680 | last8 bs | 760 | last8 bs |
681 | | let len = B.length bs | 761 | | let len = B.length bs |
@@ -688,6 +768,16 @@ last8 bs | |||
688 | 768 | ||
689 | dropEnd8 :: ByteString -> ByteString | 769 | dropEnd8 :: ByteString -> ByteString |
690 | dropEnd8 bs = B.take (B.length bs - 8) bs | 770 | dropEnd8 bs = B.take (B.length bs - 8) bs |
771 | -} | ||
772 | |||
773 | data Payload a = Payload | ||
774 | { payload :: a | ||
775 | , sendback :: Nonce8 | ||
776 | } | ||
777 | |||
778 | instance S.Serialize a => S.Serialize (Payload a) where | ||
779 | get = Payload <$> S.get <*> S.get | ||
780 | put (Payload a nonce) = S.put a >> S.put nonce | ||
691 | 781 | ||
692 | 782 | ||
693 | -- Add detailed printouts for every packet. | 783 | -- Add detailed printouts for every packet. |
@@ -699,14 +789,29 @@ addVerbosity tr = | |||
699 | kont m | 789 | kont m |
700 | , sendMessage = \addr msg -> do | 790 | , sendMessage = \addr msg -> do |
701 | hPutStrLn stderr ( (show addr) | 791 | hPutStrLn stderr ( (show addr) |
702 | ++ " <-- " ++ show (msgType msg)) | 792 | ++ " <-- " ++ show msg ) -- (msgType msg)) |
703 | sendMessage tr addr msg | 793 | sendMessage tr addr msg |
704 | } | 794 | } |
705 | 795 | ||
706 | classify :: Message ByteString -> MessageClass String Method TransactionId | 796 | addVerbosity2 tr = |
707 | classify (Message { msgType = typ | 797 | tr { awaitMessage = \kont -> awaitMessage tr $ \m -> do |
708 | , msgPayload = bs | 798 | forM_ m $ mapM_ $ \(msg,addr) -> do |
709 | , msgNonce = nonce24 }) = go $ TransactionId (last8 bs) nonce24 | 799 | hPutStrLn stderr ( (show addr) |
800 | ++ " -2-> " ++ show (Tox.PacketKind $ B.head msg)) | ||
801 | kont m | ||
802 | , sendMessage = \addr msg -> do | ||
803 | hPutStrLn stderr ( (show addr) | ||
804 | ++ " <-2- " ++ show (Tox.PacketKind $ B.head msg)) | ||
805 | forM_ (xxd 0 msg) (hPutStrLn stderr) | ||
806 | sendMessage tr addr msg | ||
807 | } | ||
808 | |||
809 | |||
810 | classify :: Msg -> MessageClass String Tox.PacketKind TransactionId | ||
811 | classify (Msg { msgType = typ | ||
812 | , msgData = bs | ||
813 | , msgSendBack = nonce8 | ||
814 | , msgNonce = nonce24 }) = go $ TransactionId nonce8 nonce24 | ||
710 | where | 815 | where |
711 | go = case typ of | 816 | go = case typ of |
712 | PingType -> IsQuery typ | 817 | PingType -> IsQuery typ |
@@ -720,6 +825,7 @@ classify (Message { msgType = typ | |||
720 | AnnounceType -> IsQuery typ | 825 | AnnounceType -> IsQuery typ |
721 | _ -> const $ IsUnknown ("Unknown message type: "++show typ) | 826 | _ -> const $ IsUnknown ("Unknown message type: "++show typ) |
722 | 827 | ||
828 | {- | ||
723 | encodePayload typ (TransactionId (Nonce8 tid) nonce) self dest b | 829 | encodePayload typ (TransactionId (Nonce8 tid) nonce) self dest b |
724 | = Message { msgType = typ | 830 | = Message { msgType = typ |
725 | , msgOrigin = nodeId self | 831 | , msgOrigin = nodeId self |
@@ -730,18 +836,18 @@ encodePayload typ (TransactionId (Nonce8 tid) nonce) self dest b | |||
730 | 836 | ||
731 | decodePayload :: S.Serialize a => Message ByteString -> Either String a | 837 | decodePayload :: S.Serialize a => Message ByteString -> Either String a |
732 | decodePayload msg = S.decode $ dropEnd8 $ msgPayload msg | 838 | decodePayload msg = S.decode $ dropEnd8 $ msgPayload msg |
839 | -} | ||
733 | 840 | ||
734 | type Handler = MethodHandler String TransactionId NodeInfo (Message ByteString) | 841 | type Handler = MethodHandler String TransactionId NodeInfo Msg |
735 | |||
736 | handler typ f = Just $ MethodHandler decodePayload (encodePayload typ) f | ||
737 | 842 | ||
738 | noreply :: S.Serialize b => | 843 | {- |
739 | Method | 844 | noreply :: Tox.PacketKind |
740 | -> (addr -> Message b -> IO ()) | 845 | -> (addr -> Msg -> IO ()) |
741 | -> Maybe (MethodHandler String tid addr (Message ByteString)) | 846 | -> Maybe (MethodHandler String tid addr Msg) |
742 | noreply typ f = Just $ NoReply (mapM deserialize) f | 847 | noreply typ f = Just $ NoReply (mapM deserialize) f |
743 | where | 848 | where |
744 | deserialize = S.decode . bool id dropEnd8 (typeHasEncryptedPayload typ) | 849 | deserialize = S.decode . bool id dropEnd8 (typeHasEncryptedPayload typ) |
850 | -} | ||
745 | 851 | ||
746 | transitionCommittee :: TriadCommittee NodeId SockAddr -> RoutingTransition NodeInfo -> STM (IO ()) | 852 | transitionCommittee :: TriadCommittee NodeId SockAddr -> RoutingTransition NodeInfo -> STM (IO ()) |
747 | transitionCommittee committee (RoutingTransition ni Stranger) = do | 853 | transitionCommittee committee (RoutingTransition ni Stranger) = do |
@@ -750,13 +856,12 @@ transitionCommittee committee (RoutingTransition ni Stranger) = do | |||
750 | hPutStrLn stderr $ "delVote "++show (nodeId ni) | 856 | hPutStrLn stderr $ "delVote "++show (nodeId ni) |
751 | transitionCommittee committee _ = return $ return () | 857 | transitionCommittee committee _ = return $ return () |
752 | 858 | ||
753 | updateRouting :: ToxClient -> Routing -> NodeInfo -> Message ByteString -> IO () | 859 | updateRouting :: ToxClient -> Routing -> NodeInfo -> (Tox.PacketKind, Tox.Assymetric) -> IO () |
754 | updateRouting client routing addr msg = do | 860 | updateRouting client routing naddr (typ,msg) = do |
755 | forM_ (msgDHTKey msg) $ \nid -> do | 861 | hPutStrLn stderr $ "updateRouting "++show typ |
756 | let naddr = addr { nodeId = nid } | 862 | case prefer4or6 naddr Nothing of |
757 | case prefer4or6 naddr Nothing of | 863 | Want_IP4 -> updateTable client naddr (routing4 routing) (committee4 routing) (sched4 routing) |
758 | Want_IP4 -> updateTable client naddr (routing4 routing) (committee4 routing) (sched4 routing) | 864 | Want_IP6 -> updateTable client naddr (routing6 routing) (committee6 routing) (sched6 routing) |
759 | Want_IP6 -> updateTable client naddr (routing6 routing) (committee6 routing) (sched6 routing) | ||
760 | 865 | ||
761 | updateTable client naddr tbl committee sched = do | 866 | updateTable client naddr tbl committee sched = do |
762 | self <- atomically $ R.thisNode <$> readTVar tbl | 867 | self <- atomically $ R.thisNode <$> readTVar tbl |
@@ -971,7 +1076,8 @@ getNodesH routing addr (GetNodes nid) = do | |||
971 | k = 4 | 1076 | k = 4 |
972 | 1077 | ||
973 | 1078 | ||
974 | symmetricCipher :: DRG g => STM ByteString -> STM g -> (g -> STM ()) -> ByteString -> IO SymmetricCiphered | 1079 | {- |
1080 | symmetricCipher :: DRG g => STM ByteString -> STM g -> (g -> STM ()) -> ByteString -> IO (Tox.Nonce24, SymmetricCiphered) | ||
975 | symmetricCipher currentSymmetricKey readG writeG bs = (>>= \e -> hPutStrLn stderr (show e) >> Cryptonite.throwCryptoErrorIO e) $ atomically $ do | 1081 | symmetricCipher currentSymmetricKey readG writeG bs = (>>= \e -> hPutStrLn stderr (show e) >> Cryptonite.throwCryptoErrorIO e) $ atomically $ do |
976 | g <- readG | 1082 | g <- readG |
977 | let (sym_nonce_bytes, g') = randomBytesGenerate 12 g | 1083 | let (sym_nonce_bytes, g') = randomBytesGenerate 12 g |
@@ -985,9 +1091,12 @@ symmetricCipher currentSymmetricKey readG writeG bs = (>>= \e -> hPutStrLn stder | |||
985 | -- For a single SockAddr, bs will be 19 bytes which gives | 1091 | -- For a single SockAddr, bs will be 19 bytes which gives |
986 | -- 12 + 16 + 19 = 47 bytes. | 1092 | -- 12 + 16 + 19 = 47 bytes. |
987 | -- We need 12 more make 59 bytes, so we'll include the nonce twice. | 1093 | -- We need 12 more make 59 bytes, so we'll include the nonce twice. |
988 | return $ SymmetricCiphered (sym_nonce_bytes <> sym_nonce_bytes <> BA.convert auth <> rpath_bs) | 1094 | nonce24 = Tox.Nonce24 $ sym_nonce <> sym_nonce |
1095 | return ( nonce24 | ||
1096 | , SymmetricCiphered (BA.convert auth <> rpath_bs) | ||
1097 | ) | ||
989 | 1098 | ||
990 | symmetricDecipher currentSymmetricKey (Nonce24 nonce24) (SymmetricCiphered bs) = atomically $ do | 1099 | symmetricDecipher currentSymmetricKey (Tox.Nonce24 nonce24) (SymmetricCiphered bs) = atomically $ do |
991 | symmkey <- currentSymmetricKey | 1100 | symmkey <- currentSymmetricKey |
992 | return $ do | 1101 | return $ do |
993 | let sym_nonce_bytes = B.drop 12 nonce24 | 1102 | let sym_nonce_bytes = B.drop 12 nonce24 |
@@ -1000,11 +1109,12 @@ symmetricDecipher currentSymmetricKey (Nonce24 nonce24) (SymmetricCiphered bs) = | |||
1000 | if BA.convert auth /= mac | 1109 | if BA.convert auth /= mac |
1001 | then Left "symmetricDecipher: Auth fail." | 1110 | then Left "symmetricDecipher: Auth fail." |
1002 | else return $ ds | 1111 | else return $ ds |
1112 | -} | ||
1003 | 1113 | ||
1004 | 1114 | {- | |
1005 | 1115 | ||
1006 | -- OnionRequest0 | 1116 | -- OnionRequest0 |
1007 | onionSend0H :: (ByteString -> IO SymmetricCiphered) | 1117 | onionSend0H :: (ByteString -> IO (Tox.Nonce24,SymmetricCiphered)) |
1008 | -> Transport err SockAddr ByteString | 1118 | -> Transport err SockAddr ByteString |
1009 | -> NodeInfo | 1119 | -> NodeInfo |
1010 | -> Message (OnionWrap Ciphered) | 1120 | -> Message (OnionWrap Ciphered) |
@@ -1012,12 +1122,12 @@ onionSend0H :: (ByteString -> IO SymmetricCiphered) | |||
1012 | onionSend0H symcipher udp addr Message{ msgNonce | 1122 | onionSend0H symcipher udp addr Message{ msgNonce |
1013 | , msgPayload = OnionWrap forward alias ciphered } = do | 1123 | , msgPayload = OnionWrap forward alias ciphered } = do |
1014 | hPutStrLn stderr $ "onionSend0H( " ++ show addr ++ " --> " ++ either show show (either4or6 forward) ++ ")" | 1124 | hPutStrLn stderr $ "onionSend0H( " ++ show addr ++ " --> " ++ either show show (either4or6 forward) ++ ")" |
1015 | rpath <- symcipher (S.runPut $ putForwardAddr forward) | 1125 | (nonce,rpath) <- symcipher (S.runPut $ putForwardAddr forward) |
1016 | sendMessage udp forward $ S.runPut $ putMessage | 1126 | sendMessage udp forward $ S.runPut $ putMessage |
1017 | Message { msgType = OnionRequest1 | 1127 | Message { msgType = OnionRequest1 |
1018 | , msgOrigin = alias | 1128 | , msgOrigin = alias |
1019 | , msgNonce = msgNonce | 1129 | , msgNonce = msgNonce |
1020 | , msgReturnPath = Just rpath | 1130 | , msgReturnPath = Just (nonce,rpath) |
1021 | , msgPayload = Right ciphered | 1131 | , msgPayload = Right ciphered |
1022 | } | 1132 | } |
1023 | hPutStrLn stderr $ "onionSend0H SENT ( " ++ show addr ++ " --> " ++ either show show (either4or6 forward) ++ ")" | 1133 | hPutStrLn stderr $ "onionSend0H SENT ( " ++ show addr ++ " --> " ++ either show show (either4or6 forward) ++ ")" |
@@ -1026,7 +1136,7 @@ onionSend0H symcipher udp addr Message{ msgNonce | |||
1026 | -- | 1136 | -- |
1027 | -- No public-key decryption here. | 1137 | -- No public-key decryption here. |
1028 | onionResponse1H :: | 1138 | onionResponse1H :: |
1029 | (Nonce24 -> SymmetricCiphered -> IO (Either String ByteString)) | 1139 | (Tox.Nonce24 -> SymmetricCiphered -> IO (Either String ByteString)) |
1030 | -> Transport err SockAddr ByteString | 1140 | -> Transport err SockAddr ByteString |
1031 | -> NodeInfo | 1141 | -> NodeInfo |
1032 | -> Message OnionPayload | 1142 | -> Message OnionPayload |
@@ -1044,6 +1154,8 @@ onionResponse1H symdecipher udp addr Message{ msgNonce | |||
1044 | sendMessage udp forward (unpackOnionPayload msgPayload) | 1154 | sendMessage udp forward (unpackOnionPayload msgPayload) |
1045 | either (hPutStrLn stderr . mappend "onionResponse1H decipher ERROR ") (\x -> go x >> hPutStrLn stderr "onionResponse1H SENT") eaddr | 1155 | either (hPutStrLn stderr . mappend "onionResponse1H decipher ERROR ") (\x -> go x >> hPutStrLn stderr "onionResponse1H SENT") eaddr |
1046 | 1156 | ||
1157 | -} | ||
1158 | |||
1047 | intKey :: TransactionId -> Int | 1159 | intKey :: TransactionId -> Int |
1048 | intKey (TransactionId (Nonce8 w) _) = fromIntegral w | 1160 | intKey (TransactionId (Nonce8 w) _) = fromIntegral w |
1049 | 1161 | ||
@@ -1056,7 +1168,8 @@ gen :: forall gen. DRG gen => gen -> (TransactionId, gen) | |||
1056 | gen g = let (bs, g') = randomBytesGenerate 24 g | 1168 | gen g = let (bs, g') = randomBytesGenerate 24 g |
1057 | (ws, g'') = randomBytesGenerate 8 g' | 1169 | (ws, g'') = randomBytesGenerate 8 g' |
1058 | Right w = S.runGet S.getWord64be ws | 1170 | Right w = S.runGet S.getWord64be ws |
1059 | in ( TransactionId (Nonce8 w) (Nonce24 bs), g'' ) | 1171 | in ( TransactionId (Nonce8 w) (Tox.Nonce24 bs), g'' ) |
1172 | |||
1060 | 1173 | ||
1061 | 1174 | ||
1062 | toxSend meth unwrap msg client nid addr = do | 1175 | toxSend meth unwrap msg client nid addr = do |
@@ -1072,7 +1185,7 @@ toxSend meth unwrap msg client nid addr = do | |||
1072 | -- wrapQuery :: tid -> addr -> addr -> a -> x | 1185 | -- wrapQuery :: tid -> addr -> addr -> a -> x |
1073 | , wrapQuery = encodePayload meth | 1186 | , wrapQuery = encodePayload meth |
1074 | -- unwrapResponse :: x -> b | 1187 | -- unwrapResponse :: x -> b |
1075 | , unwrapResponse = fmap unwrap . decodePayload | 1188 | , unwrapResponse = fmap unwrap . S.decode . msgData |
1076 | } | 1189 | } |
1077 | 1190 | ||
1078 | ping :: ToxClient -> NodeInfo -> IO Bool | 1191 | ping :: ToxClient -> NodeInfo -> IO Bool |
@@ -1092,3 +1205,4 @@ toxSearch qry = Search | |||
1092 | } | 1205 | } |
1093 | 1206 | ||
1094 | nodeSearch client = toxSearch (getNodes client) | 1207 | nodeSearch client = toxSearch (getNodes client) |
1208 | |||