diff options
author | joe <joe@jerkface.net> | 2017-08-05 23:45:31 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-08-05 23:45:31 -0400 |
commit | aa5ea9e2049c741140773d2adf0f0daea236d913 (patch) | |
tree | 89f9227b9377f876d52be52b506a9ff7f0cca3f3 /Tox.hs | |
parent | 28801136a43bc1600953d5ccca69d830d83f1eba (diff) |
Implemented Tox's announce handler.
Diffstat (limited to 'Tox.hs')
-rw-r--r-- | Tox.hs | 362 |
1 files changed, 252 insertions, 110 deletions
@@ -7,71 +7,78 @@ | |||
7 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 7 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
8 | {-# LANGUAGE NamedFieldPuns #-} | 8 | {-# LANGUAGE NamedFieldPuns #-} |
9 | {-# LANGUAGE PatternSynonyms #-} | 9 | {-# LANGUAGE PatternSynonyms #-} |
10 | {-# LANGUAGE RankNTypes #-} | ||
10 | {-# LANGUAGE ScopedTypeVariables #-} | 11 | {-# LANGUAGE ScopedTypeVariables #-} |
11 | {-# LANGUAGE TupleSections #-} | 12 | {-# LANGUAGE TupleSections #-} |
12 | module Tox where | 13 | module Tox where |
13 | 14 | ||
14 | import Control.Applicative | 15 | import Control.Applicative |
15 | import Control.Arrow | 16 | import Control.Arrow |
16 | import Control.Concurrent (MVar) | 17 | import Control.Concurrent (MVar) |
17 | import Control.Concurrent.STM | 18 | import Control.Concurrent.STM |
18 | import qualified Crypto.Cipher.Salsa as Salsa | 19 | import Control.Monad |
19 | import qualified Crypto.Cipher.XSalsa as XSalsa | 20 | import qualified Crypto.Cipher.ChaChaPoly1305 as Symmetric |
21 | import qualified Crypto.Cipher.Salsa as Salsa | ||
22 | import qualified Crypto.Cipher.XSalsa as XSalsa | ||
20 | import Crypto.ECC.Class | 23 | import Crypto.ECC.Class |
21 | import qualified Crypto.Error as Cryptonite | 24 | import qualified Crypto.Error as Cryptonite |
22 | import Crypto.Error.Types | 25 | import Crypto.Error.Types |
23 | import qualified Crypto.MAC.Poly1305 as Poly1305 | 26 | import qualified Crypto.MAC.Poly1305 as Poly1305 |
24 | import Crypto.PubKey.Curve25519 | 27 | import Crypto.PubKey.Curve25519 |
25 | import Crypto.PubKey.ECC.Types | 28 | import Crypto.PubKey.ECC.Types |
26 | import Crypto.Random | 29 | import Crypto.Random |
30 | import qualified Data.Aeson as JSON | ||
31 | ;import Data.Aeson (FromJSON, ToJSON, (.=)) | ||
32 | import Data.Bitraversable (bisequence) | ||
33 | import Data.Bits | ||
34 | import Data.Bits.ByteString () | ||
27 | import Data.Bool | 35 | import Data.Bool |
28 | import qualified Data.ByteArray as BA | 36 | import qualified Data.ByteArray as BA |
29 | ;import Data.ByteArray (ByteArrayAccess,Bytes) | 37 | ;import Data.ByteArray (ByteArrayAccess, Bytes) |
30 | import qualified Data.ByteString as B | 38 | import qualified Data.ByteString as B |
31 | ;import Data.ByteString (ByteString) | 39 | ;import Data.ByteString (ByteString) |
32 | import qualified Data.ByteString.Base16 as Base16 | 40 | import qualified Data.ByteString.Base16 as Base16 |
33 | import qualified Data.ByteString.Char8 as C8 | 41 | import qualified Data.ByteString.Char8 as C8 |
34 | import Data.ByteString.Lazy (toStrict) | 42 | import Data.ByteString.Lazy (toStrict) |
43 | import Data.Char | ||
35 | import Data.Data | 44 | import Data.Data |
45 | import Data.Hashable | ||
36 | import Data.IP | 46 | import Data.IP |
37 | import Data.Maybe | 47 | import Data.Maybe |
48 | import qualified Data.MinMaxPSQ as MinMaxPSQ | ||
49 | ;import Data.MinMaxPSQ (MinMaxPSQ') | ||
38 | import Data.Monoid | 50 | import Data.Monoid |
39 | import qualified Data.Serialize as S | 51 | import Data.Ord |
52 | import qualified Data.Serialize as S | ||
53 | import Data.Time.Clock.POSIX (POSIXTime, getPOSIXTime) | ||
40 | import Data.Typeable | 54 | import Data.Typeable |
41 | import Data.Word | 55 | import Data.Word |
56 | import qualified Data.Wrapper.PSQ as PSQ | ||
57 | ;import Data.Wrapper.PSQ (PSQ) | ||
58 | import qualified Data.Wrapper.PSQInt as Int | ||
42 | import Foreign.Marshal.Alloc | 59 | import Foreign.Marshal.Alloc |
43 | import Foreign.Ptr | 60 | import Foreign.Ptr |
44 | import Foreign.Storable | 61 | import Foreign.Storable |
45 | import GHC.Generics (Generic) | 62 | import GHC.Generics (Generic) |
46 | import Network.Address (Address, fromSockAddr, sockAddrPort, testIdBit, | 63 | import Global6 |
47 | toSockAddr, setPort, un4map, WantIP(..), ipFamily, | 64 | import Kademlia |
48 | either4or6) | 65 | import Network.Address (Address, WantIP (..), either4or6, |
66 | fromSockAddr, ipFamily, setPort, | ||
67 | sockAddrPort, testIdBit, | ||
68 | toSockAddr, un4map) | ||
69 | import Network.BitTorrent.DHT.Search (Search (..)) | ||
70 | import qualified Network.DHT.Routing as R | ||
49 | import Network.QueryResponse | 71 | import Network.QueryResponse |
50 | import Network.Socket | 72 | import Network.Socket |
51 | import System.Endian | 73 | import System.Endian |
52 | import Data.Hashable | ||
53 | import Data.Bits | ||
54 | import Data.Bits.ByteString () | ||
55 | import qualified Text.ParserCombinators.ReadP as RP | ||
56 | import Data.Char | ||
57 | import TriadCommittee | ||
58 | import qualified Network.DHT.Routing as R | ||
59 | import qualified Data.Wrapper.PSQInt as Int | ||
60 | import Data.Time.Clock.POSIX (POSIXTime) | ||
61 | import Global6 | ||
62 | import Data.Ord | ||
63 | import System.IO | 74 | import System.IO |
64 | import qualified Data.Aeson as JSON | 75 | import qualified Text.ParserCombinators.ReadP as RP |
65 | ;import Data.Aeson (FromJSON, ToJSON, (.=)) | ||
66 | import Control.Monad | ||
67 | import Text.Read | ||
68 | import Kademlia | ||
69 | import Network.BitTorrent.DHT.Search (Search (..)) | ||
70 | import Text.Printf | 76 | import Text.Printf |
71 | import qualified Crypto.Cipher.ChaChaPoly1305 as Symmetric | 77 | import Text.Read |
72 | import Data.Bitraversable (bisequence) | 78 | import qualified ToxMessage as Tox |
73 | import ToxMessage (quoted,bin2hex) | 79 | ;import ToxMessage (bin2hex, quoted) |
74 | import qualified ToxMessage as Tox | 80 | import TriadCommittee |
81 | import Network.BitTorrent.DHT.Token as Token | ||
75 | 82 | ||
76 | {- | 83 | {- |
77 | newtype NodeId = NodeId ByteString | 84 | newtype NodeId = NodeId ByteString |
@@ -224,7 +231,7 @@ nodeInfo nid saddr | |||
224 | | otherwise = Left "Address family not supported." | 231 | | otherwise = Left "Address family not supported." |
225 | 232 | ||
226 | data TransactionId = TransactionId | 233 | data TransactionId = TransactionId |
227 | { transactionKey :: Nonce8 -- ^ Used to lookup pending query. | 234 | { transactionKey :: Tox.Nonce8 -- ^ Used to lookup pending query. |
228 | , cryptoNonce :: Tox.Nonce24 -- ^ Used during the encryption layer. | 235 | , cryptoNonce :: Tox.Nonce24 -- ^ Used during the encryption layer. |
229 | } | 236 | } |
230 | 237 | ||
@@ -247,8 +254,7 @@ pattern OnionRequest0 = Tox.PacketKind 128 -- 0x80 Onion Request 0 | |||
247 | pattern OnionRequest1 = Tox.PacketKind 129 -- 0x81 Onion Request 1 | 254 | pattern OnionRequest1 = Tox.PacketKind 129 -- 0x81 Onion Request 1 |
248 | pattern OnionRequest2 = Tox.PacketKind 130 -- 0x82 Onion Request 2 | 255 | pattern OnionRequest2 = Tox.PacketKind 130 -- 0x82 Onion Request 2 |
249 | pattern AnnounceType = Tox.PacketKind 131 -- 0x83 Announce Request | 256 | pattern AnnounceType = Tox.PacketKind 131 -- 0x83 Announce Request |
250 | 257 | pattern AnnounceResponseType = Tox.PacketKind 132 -- 0x84 Announce Response | |
251 | -- 0x84 Announce Response | ||
252 | -- 0x85 Onion Data Request (data to route request packet) | 258 | -- 0x85 Onion Data Request (data to route request packet) |
253 | -- 0x86 Onion Data Response (data to route response packet) | 259 | -- 0x86 Onion Data Response (data to route response packet) |
254 | -- 0x8c Onion Response 3 | 260 | -- 0x8c Onion Response 3 |
@@ -276,19 +282,6 @@ instance Show Tox.PacketKind where | |||
276 | showsPrec d AnnounceType = mappend "AnnounceType" | 282 | showsPrec d AnnounceType = mappend "AnnounceType" |
277 | showsPrec d (Tox.PacketKind x) = mappend "PacketKind " . showsPrec (d+1) x | 283 | showsPrec d (Tox.PacketKind x) = mappend "PacketKind " . showsPrec (d+1) x |
278 | 284 | ||
279 | newtype Nonce8 = Nonce8 Word64 | ||
280 | deriving (Eq, Ord, S.Serialize) | ||
281 | |||
282 | instance ByteArrayAccess Nonce8 where | ||
283 | length _ = 8 | ||
284 | withByteArray (Nonce8 w64) kont = | ||
285 | allocaBytes 8 $ \p -> do | ||
286 | poke (castPtr p :: Ptr Word64) $ toBE64 w64 | ||
287 | kont p | ||
288 | |||
289 | instance Show Nonce8 where | ||
290 | showsPrec d nonce = quoted (mappend $ bin2hex nonce) | ||
291 | |||
292 | {- | 285 | {- |
293 | newtype Tox.Nonce24 = Tox.Nonce24 ByteString | 286 | newtype Tox.Nonce24 = Tox.Nonce24 ByteString |
294 | deriving (Eq, Ord, ByteArrayAccess) | 287 | deriving (Eq, Ord, ByteArrayAccess) |
@@ -319,7 +312,7 @@ data Msg = Msg | |||
319 | { msgType :: Tox.PacketKind | 312 | { msgType :: Tox.PacketKind |
320 | , msgNonce :: Tox.Nonce24 | 313 | , msgNonce :: Tox.Nonce24 |
321 | , msgData :: ByteString | 314 | , msgData :: ByteString |
322 | , msgSendBack :: Nonce8 | 315 | , msgSendBack :: Tox.Nonce8 |
323 | } | 316 | } |
324 | deriving Show | 317 | deriving Show |
325 | 318 | ||
@@ -400,7 +393,7 @@ putMessage (Message {..}) = do | |||
400 | 393 | ||
401 | {- | 394 | {- |
402 | data Plain a = Plain | 395 | data Plain a = Plain |
403 | { plainId :: Nonce8 -- transactionKey of TransactionId | 396 | { plainId :: Tox.Nonce8 -- transactionKey of TransactionId |
404 | , plainPayload :: a | 397 | , plainPayload :: a |
405 | } | 398 | } |
406 | deriving (Eq, Show, Generic, Functor, Foldable, Traversable) | 399 | deriving (Eq, Show, Generic, Functor, Foldable, Traversable) |
@@ -426,11 +419,11 @@ key2id pk = case S.decode (BA.convert pk) of | |||
426 | Right nid -> nid | 419 | Right nid -> nid |
427 | 420 | ||
428 | 421 | ||
429 | zeros32 :: Bytes | 422 | zeros32 :: Nonce32 |
430 | zeros32 = BA.replicate 32 0 | 423 | zeros32 = Nonce32 $ BA.replicate 32 0 |
431 | 424 | ||
432 | zeros24 :: Bytes | 425 | zeros24 :: ByteString |
433 | zeros24 = BA.take 24 zeros32 | 426 | zeros24 = BA.take 24 zs where Nonce32 zs = zeros32 |
434 | 427 | ||
435 | hsalsa20 k n = a <> b | 428 | hsalsa20 k n = a <> b |
436 | where | 429 | where |
@@ -451,7 +444,7 @@ computeSharedSecret sk recipient nonce = (hash, crypt) | |||
451 | -- cipher state | 444 | -- cipher state |
452 | st0 = XSalsa.initialize 20 k nonce | 445 | st0 = XSalsa.initialize 20 k nonce |
453 | -- Poly1305 key | 446 | -- Poly1305 key |
454 | (rs, crypt) = XSalsa.combine st0 zeros32 | 447 | (rs, crypt) = XSalsa.combine st0 zs where Nonce32 zs = zeros32 |
455 | -- Since rs is 32 bytes, this pattern should never fail... | 448 | -- Since rs is 32 bytes, this pattern should never fail... |
456 | Cryptonite.CryptoPassed hash = Poly1305.initialize rs | 449 | Cryptonite.CryptoPassed hash = Poly1305.initialize rs |
457 | 450 | ||
@@ -464,16 +457,25 @@ encryptMessage sk _ recipient plaintext | |||
464 | else Left . OnionPayload <$> plaintext | 457 | else Left . OnionPayload <$> plaintext |
465 | -} | 458 | -} |
466 | 459 | ||
467 | encryptAssymetric :: SecretKey -> NodeId -> NodeId -> Msg -> (Tox.PacketKind, Tox.Assymetric) | 460 | encryptAssymetric :: SecretKey -> NodeId -> NodeId -> Msg -> Tox.Assymetric |
468 | encryptAssymetric sk pk recipient (Msg typ nonce plaintext sendback) | 461 | encryptAssymetric sk pk recipient (Msg typ nonce plaintext sendback) = assym |
469 | = ( typ | 462 | where |
470 | , Tox.Assymetric | 463 | assym = Tox.Assymetric |
471 | { senderKey = pk | 464 | { senderKey = pk |
472 | , sent = Tox.UnclaimedAssymetric | 465 | , sent = Tox.UnclaimedAssymetric |
473 | { assymetricNonce = nonce | 466 | { assymetricNonce = nonce |
474 | , assymetricData = withSecret encipherAndHash sk recipient nonce (plaintext <> S.encode sendback) | 467 | , assymetricData = withSecret encipherAndHash sk recipient nonce (plaintext <> S.encode sendback) |
475 | } | 468 | } |
476 | } ) | 469 | } |
470 | |||
471 | encryptUnclm :: SecretKey -> NodeId -> NodeId -> Msg -> Tox.UnclaimedAssymetric | ||
472 | encryptUnclm sk pk recipient (Msg typ nonce plaintext _) = unclm | ||
473 | where | ||
474 | unclm = Tox.UnclaimedAssymetric | ||
475 | { assymetricNonce = nonce | ||
476 | , assymetricData = withSecret encipherAndHash sk recipient nonce plaintext | ||
477 | } | ||
478 | |||
477 | 479 | ||
478 | {- | 480 | {- |
479 | decryptMessage :: SecretKey -> SecretsCache -> Message Ciphered -> Either String (Message ByteString) | 481 | decryptMessage :: SecretKey -> SecretsCache -> Message Ciphered -> Either String (Message ByteString) |
@@ -481,15 +483,29 @@ decryptMessage sk _ ciphertext | |||
481 | = mapM (withSecret decipherAndAuth sk (msgOrigin ciphertext) (msgNonce ciphertext)) ciphertext | 483 | = mapM (withSecret decipherAndAuth sk (msgOrigin ciphertext) (msgNonce ciphertext)) ciphertext |
482 | -} | 484 | -} |
483 | 485 | ||
484 | decryptAssymetric :: SecretKey -> (Tox.PacketKind, Tox.Assymetric) -> Either String Msg | 486 | decryptAssymetric :: SecretKey -> Tox.PacketKind -> Tox.Assymetric -> Either String Msg |
485 | decryptAssymetric sk (typ,assym) | 487 | decryptAssymetric sk typ assym |
486 | = f <$> withSecret decipherAndAuth sk | 488 | = f <$> withSecret decipherAndAuth sk |
487 | (Tox.senderKey assym) | 489 | (Tox.senderKey assym) |
488 | nonce | 490 | nonce |
489 | (Tox.assymetricData . Tox.sent $ assym) | 491 | (Tox.assymetricData . Tox.sent $ assym) |
490 | where | 492 | where |
491 | nonce = Tox.assymetricNonce . Tox.sent $ assym | 493 | 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 | 494 | f bs = uncurry (Msg typ nonce) |
495 | . second (either (const (Tox.Nonce8 0)) id . S.decode) | ||
496 | $ B.splitAt (B.length bs - 8) bs | ||
497 | |||
498 | {- | ||
499 | decryptUnclm :: SecretKey -> Tox.PacketKind -> NodeId -> Tox.Nonce8 -> Tox.UnclaimedAssymetric -> Either String Msg | ||
500 | decryptUnclm sk typ sender n8 unclm | ||
501 | = f <$> withSecret decipherAndAuth sk | ||
502 | sender | ||
503 | nonce | ||
504 | (Tox.assymetricData unclm) | ||
505 | where | ||
506 | nonce = Tox.assymetricNonce unclm | ||
507 | f bs = Msg typ nonce bs n8 | ||
508 | -} | ||
493 | 509 | ||
494 | withSecret f sk recipient nonce x = f hash crypt x | 510 | withSecret f sk recipient nonce x = f hash crypt x |
495 | where | 511 | where |
@@ -544,7 +560,7 @@ unzipMessage msg = either (\x -> Left msg { msgPayload = x }) | |||
544 | 560 | ||
545 | -- TODO: | 561 | -- TODO: |
546 | -- Represents the encrypted portion of a Tox packet. | 562 | -- Represents the encrypted portion of a Tox packet. |
547 | -- data Payload a = Payload a !Nonce8 | 563 | -- data Payload a = Payload a !Tox.Nonce8 |
548 | -- | 564 | -- |
549 | -- Generic packet type: Message (Payload ByteString) | 565 | -- Generic packet type: Message (Payload ByteString) |
550 | 566 | ||
@@ -565,22 +581,40 @@ encodePacket sk cache msg ni = ( S.runPut . putMessage $ encryptMessage sk cache | |||
565 | 581 | ||
566 | msgLayer :: SecretKey | 582 | msgLayer :: SecretKey |
567 | -> NodeId | 583 | -> NodeId |
568 | -> Transport String NodeInfo (Tox.PacketKind,Tox.Assymetric) | 584 | -> Transport String NodeInfo (Tox.PacketKind,InterediateRep) |
569 | -> Transport String NodeInfo Msg | 585 | -> Transport String NodeInfo Msg |
570 | msgLayer sk pk = layerTransport parse serialize | 586 | msgLayer sk pk = layerTransport parse serialize |
571 | where | 587 | where |
572 | parse x addr = fmap (,addr) $ decryptAssymetric sk x | 588 | parse (typ,Assym x) addr = fmap (,addr) $ decryptAssymetric sk typ x |
573 | serialize x addr = (encryptAssymetric sk pk (nodeId addr) x, addr) | 589 | parse (typ,Assym' x) addr = fmap (,addr) $ decryptAssymetric sk typ x |
574 | 590 | parse (typ,Unclm n x) addr = Right ( Msg typ (Tox.assymetricNonce x) (S.encode (Tox.assymetricData x)) n | |
575 | asymLayer :: Transport String SockAddr Tox.Packet -> Transport String NodeInfo (Tox.PacketKind,Tox.Assymetric) | 591 | , addr) |
592 | serialize x addr = case Tox.pktClass (msgType x) of | ||
593 | Tox.AssymetricClass {} -> ((msgType x, Assym $ encryptAssymetric sk pk (nodeId addr) x), addr) | ||
594 | Tox.AliasedClass {} -> ((msgType x, Assym' $ encryptAssymetric sk pk (nodeId addr) x), addr) | ||
595 | Tox.NoncedUnclaimedClass {} -> ((msgType x, Unclm (msgSendBack x) $ encryptUnclm sk pk (nodeId addr) x),addr) | ||
596 | |||
597 | data InterediateRep = Assym Tox.Assymetric | ||
598 | | Assym' Tox.Assymetric | ||
599 | | Unclm Tox.Nonce8 Tox.UnclaimedAssymetric | ||
600 | |||
601 | asymLayer :: Transport String SockAddr Tox.Packet -> Transport String NodeInfo (Tox.PacketKind,InterediateRep) | ||
576 | asymLayer = layerTransport parse serialize | 602 | asymLayer = layerTransport parse serialize |
577 | where | 603 | where |
578 | parse x addr = case Tox.pktClass (Tox.pktKind x) of | 604 | 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 | 605 | Tox.AssymetricClass top fromp -> go Tox.senderKey fromp Assym |
580 | 606 | Tox.AliasedClass top fromp -> go Tox.senderKey ((\(Tox.Aliased a) -> a) . fromp) Assym' | |
581 | serialize (typ,assym) addr = (x,nodeAddr addr) | 607 | Tox.NoncedUnclaimedClass top fromp -> go (const zeroID) fromp (uncurry Unclm) |
582 | where x = case Tox.pktClass typ of | 608 | where go mkaddr fromp c = let y = fromp x |
583 | Tox.AssymetricClass top _ -> top assym | 609 | in fmap ((Tox.pktKind x,c y),) |
610 | $ nodeInfo (mkaddr y) addr | ||
611 | |||
612 | serialize (typ,Assym assym) addr = (x,nodeAddr addr) | ||
613 | where x = case Tox.pktClass typ of Tox.AssymetricClass top _ -> top assym | ||
614 | serialize (typ,Assym' assym) addr = (x,nodeAddr addr) | ||
615 | where x = case Tox.pktClass typ of Tox.AliasedClass top _ -> top (Tox.Aliased assym) | ||
616 | serialize (typ,Unclm nonce unclm) addr = (x,nodeAddr addr) | ||
617 | where x = case Tox.pktClass typ of Tox.NoncedUnclaimedClass top _ -> top nonce unclm | ||
584 | 618 | ||
585 | toxLayer :: Transport String SockAddr ByteString -> Transport String SockAddr Tox.Packet | 619 | toxLayer :: Transport String SockAddr ByteString -> Transport String SockAddr Tox.Packet |
586 | toxLayer = layerTransport (\x addr -> (,addr) <$> S.decode x) | 620 | toxLayer = layerTransport (\x addr -> (,addr) <$> S.decode x) |
@@ -605,11 +639,13 @@ trimPackets :: SockAddr -> ByteString -> IO (Maybe (ByteString -> ByteString)) | |||
605 | trimPackets addr bs = do | 639 | trimPackets addr bs = do |
606 | hPutStrLn stderr $ "GOT " ++ show (Tox.PacketKind (B.head bs)) | 640 | hPutStrLn stderr $ "GOT " ++ show (Tox.PacketKind (B.head bs)) |
607 | return $ case Tox.PacketKind (B.head bs) of | 641 | return $ case Tox.PacketKind (B.head bs) of |
608 | PingType -> Just id | 642 | PingType -> Just id |
609 | PongType -> Just id | 643 | PongType -> Just id |
610 | SendNodesType -> Just id | 644 | SendNodesType -> Just id |
611 | GetNodesType -> Just id | 645 | GetNodesType -> Just id |
612 | _ -> Nothing | 646 | AnnounceType -> Just id |
647 | AnnounceResponseType -> Just id | ||
648 | _ -> Nothing | ||
613 | 649 | ||
614 | newClient :: SockAddr -> IO (ToxClient, Routing) | 650 | newClient :: SockAddr -> IO (ToxClient, Routing) |
615 | newClient addr = do | 651 | newClient addr = do |
@@ -664,18 +700,23 @@ newClient addr = do | |||
664 | let mapT = transactionMethods (contramapT nonceKey mapMethods) gen | 700 | let mapT = transactionMethods (contramapT nonceKey mapMethods) gen |
665 | map_var <- atomically $ newTVar (drg, mempty) | 701 | map_var <- atomically $ newTVar (drg, mempty) |
666 | return $ Left (mapT,map_var) | 702 | return $ Left (mapT,map_var) |
703 | keydb <- atomically $ newTVar $ AnnouncedKeys PSQ.empty MinMaxPSQ.empty | ||
704 | toks <- do | ||
705 | nil <- nullSessionTokens | ||
706 | atomically $ newTVar nil { maxInterval = 20 } -- 20 second timeout on announce ping-ids. | ||
667 | let net = addHandler (handleMessage client) | 707 | let net = addHandler (handleMessage client) |
668 | $ addVerbosity | 708 | $ addVerbosity |
669 | $ msgLayer secret pubkey | 709 | $ msgLayer secret pubkey |
670 | $ onInbound (updateRouting client routing) | 710 | $ onInbound (updateRouting client routing) |
671 | $ asymLayer | 711 | $ asymLayer |
712 | -- $ addHandler (handleMessage aclient) | ||
672 | $ toxLayer | 713 | $ toxLayer |
673 | $ addVerbosity2 | 714 | $ addVerbosity2 |
674 | $ addHandler trimPackets udp | 715 | $ addHandler trimPackets udp |
675 | 716 | ||
676 | dispatch tbl var = DispatchMethods | 717 | dispatch tbl var handlers = DispatchMethods |
677 | { classifyInbound = classify | 718 | { classifyInbound = classify |
678 | , lookupHandler = handlers var | 719 | , lookupHandler = handlers -- var |
679 | , tableMethods = tbl | 720 | , tableMethods = tbl |
680 | } | 721 | } |
681 | 722 | ||
@@ -685,8 +726,11 @@ newClient addr = do | |||
685 | 726 | ||
686 | 727 | ||
687 | -- handlers :: TVar -> Method -> Maybe Handler | 728 | -- handlers :: TVar -> Method -> Maybe Handler |
688 | handlers var PingType = handler PongType pingH | 729 | -- handlers :: forall h u. (TVar (h, u (MVar Msg)) -> Tox.PacketKind -> Maybe Handler) |
689 | handlers var GetNodesType = handler SendNodesType $ getNodesH routing | 730 | handlers :: Tox.PacketKind -> Maybe Handler |
731 | handlers PingType = handler PongType pingH | ||
732 | handlers GetNodesType = handler SendNodesType $ getNodesH routing | ||
733 | handlers AnnounceType = handler AnnounceResponseType $ announceH routing toks keydb | ||
690 | {- | 734 | {- |
691 | handlers var OnionRequest0 = noreply OnionRequest0 | 735 | handlers var OnionRequest0 = noreply OnionRequest0 |
692 | $ onionSend0H (symmetricCipher (return symkey) | 736 | $ onionSend0H (symmetricCipher (return symkey) |
@@ -697,28 +741,33 @@ newClient addr = do | |||
697 | $ onionResponse1H (symmetricDecipher (return symkey)) | 741 | $ onionResponse1H (symmetricDecipher (return symkey)) |
698 | udp | 742 | udp |
699 | -} | 743 | -} |
700 | handlers var _ = Nothing | 744 | handlers _ = Nothing |
701 | -- TODO DHTRequest public key (onion) | 745 | -- TODO DHTRequest public key (onion) |
702 | -- TODO DHTRequest NAT ping | 746 | -- TODO DHTRequest NAT ping |
703 | -- TODO BootstrapInfo 0xf0 | 747 | -- TODO BootstrapInfo 0xf0 |
704 | 748 | ||
749 | announceHandlers _ = Nothing | ||
750 | |||
705 | genNonce24 var (TransactionId nonce8 _) = atomically $ do | 751 | genNonce24 var (TransactionId nonce8 _) = atomically $ do |
706 | (g,pending) <- readTVar var | 752 | (g,pending) <- readTVar var |
707 | let (bs, g') = randomBytesGenerate 24 g | 753 | let (bs, g') = randomBytesGenerate 24 g |
708 | writeTVar var (g',pending) | 754 | writeTVar var (g',pending) |
709 | return $ TransactionId nonce8 (Tox.Nonce24 bs) | 755 | return $ TransactionId nonce8 (Tox.Nonce24 bs) |
710 | 756 | ||
711 | client = either mkclient mkclient tblvar | 757 | client = either mkclient mkclient tblvar handlers |
712 | 758 | ||
713 | mkclient :: DRG g => | 759 | mkclient :: DRG g => |
714 | ( TransactionMethods (g,t (MVar Msg)) | 760 | ( TransactionMethods (g,t (MVar Msg)) |
715 | TransactionId | 761 | TransactionId |
716 | Msg | 762 | Msg |
717 | , TVar (g, t (MVar Msg)) | 763 | , TVar (g, t (MVar Msg)) |
718 | ) -> ToxClient | 764 | ) |
719 | mkclient (tbl,var) = Client | 765 | -- -> (forall h u. (TVar (h, u (MVar Msg)) -> Tox.PacketKind -> Maybe Handler)) |
766 | -> (Tox.PacketKind -> Maybe Handler) | ||
767 | -> ToxClient | ||
768 | mkclient (tbl,var) handlers = Client | ||
720 | { clientNet = net | 769 | { clientNet = net |
721 | , clientDispatcher = dispatch tbl var | 770 | , clientDispatcher = dispatch tbl var handlers |
722 | , clientErrorReporter = (printErrors stderr) { reportTimeout = reportTimeout ignoreErrors } | 771 | , clientErrorReporter = (printErrors stderr) { reportTimeout = reportTimeout ignoreErrors } |
723 | , clientPending = var | 772 | , clientPending = var |
724 | , clientAddress = \maddr -> atomically $ do | 773 | , clientAddress = \maddr -> atomically $ do |
@@ -756,15 +805,15 @@ toxSpace = R.KademliaSpace | |||
756 | 805 | ||
757 | 806 | ||
758 | {- | 807 | {- |
759 | last8 :: ByteString -> Nonce8 | 808 | last8 :: ByteString -> Tox.Nonce8 |
760 | last8 bs | 809 | last8 bs |
761 | | let len = B.length bs | 810 | | let len = B.length bs |
762 | , (len >= 8) | 811 | , (len >= 8) |
763 | = Nonce8 $ let bs' = B.drop (len - 8) bs | 812 | = Tox.Nonce8 $ let bs' = B.drop (len - 8) bs |
764 | Right w = S.runGet S.getWord64be bs' | 813 | Right w = S.runGet S.getWord64be bs' |
765 | in w | 814 | in w |
766 | | otherwise | 815 | | otherwise |
767 | = Nonce8 0 | 816 | = Tox.Nonce8 0 |
768 | 817 | ||
769 | dropEnd8 :: ByteString -> ByteString | 818 | dropEnd8 :: ByteString -> ByteString |
770 | dropEnd8 bs = B.take (B.length bs - 8) bs | 819 | dropEnd8 bs = B.take (B.length bs - 8) bs |
@@ -772,7 +821,7 @@ dropEnd8 bs = B.take (B.length bs - 8) bs | |||
772 | 821 | ||
773 | data Payload a = Payload | 822 | data Payload a = Payload |
774 | { payload :: a | 823 | { payload :: a |
775 | , sendback :: Nonce8 | 824 | , sendback :: Tox.Nonce8 |
776 | } | 825 | } |
777 | 826 | ||
778 | instance S.Serialize a => S.Serialize (Payload a) where | 827 | instance S.Serialize a => S.Serialize (Payload a) where |
@@ -826,7 +875,7 @@ classify (Msg { msgType = typ | |||
826 | _ -> const $ IsUnknown ("Unknown message type: "++show typ) | 875 | _ -> const $ IsUnknown ("Unknown message type: "++show typ) |
827 | 876 | ||
828 | {- | 877 | {- |
829 | encodePayload typ (TransactionId (Nonce8 tid) nonce) self dest b | 878 | encodePayload typ (TransactionId (Tox.Nonce8 tid) nonce) self dest b |
830 | = Message { msgType = typ | 879 | = Message { msgType = typ |
831 | , msgOrigin = nodeId self | 880 | , msgOrigin = nodeId self |
832 | , msgNonce = nonce | 881 | , msgNonce = nonce |
@@ -856,12 +905,13 @@ transitionCommittee committee (RoutingTransition ni Stranger) = do | |||
856 | hPutStrLn stderr $ "delVote "++show (nodeId ni) | 905 | hPutStrLn stderr $ "delVote "++show (nodeId ni) |
857 | transitionCommittee committee _ = return $ return () | 906 | transitionCommittee committee _ = return $ return () |
858 | 907 | ||
859 | updateRouting :: ToxClient -> Routing -> NodeInfo -> (Tox.PacketKind, Tox.Assymetric) -> IO () | 908 | updateRouting :: ToxClient -> Routing -> NodeInfo -> (Tox.PacketKind, InterediateRep) -> IO () |
860 | updateRouting client routing naddr (typ,msg) = do | 909 | updateRouting client routing naddr (typ,Assym msg) = do |
861 | hPutStrLn stderr $ "updateRouting "++show typ | 910 | hPutStrLn stderr $ "updateRouting "++show typ |
862 | case prefer4or6 naddr Nothing of | 911 | case prefer4or6 naddr Nothing of |
863 | Want_IP4 -> updateTable client naddr (routing4 routing) (committee4 routing) (sched4 routing) | 912 | Want_IP4 -> updateTable client naddr (routing4 routing) (committee4 routing) (sched4 routing) |
864 | Want_IP6 -> updateTable client naddr (routing6 routing) (committee6 routing) (sched6 routing) | 913 | Want_IP6 -> updateTable client naddr (routing6 routing) (committee6 routing) (sched6 routing) |
914 | updateRouting _ _ _ _ = return () | ||
865 | 915 | ||
866 | updateTable client naddr tbl committee sched = do | 916 | updateTable client naddr tbl committee sched = do |
867 | self <- atomically $ R.thisNode <$> readTVar tbl | 917 | self <- atomically $ R.thisNode <$> readTVar tbl |
@@ -1034,12 +1084,47 @@ putCiphered (Ciphered (Poly1305.Auth mac) bs) = do | |||
1034 | S.putByteString (BA.convert mac) | 1084 | S.putByteString (BA.convert mac) |
1035 | S.putByteString bs | 1085 | S.putByteString bs |
1036 | 1086 | ||
1037 | data Announce = Announce | 1087 | newtype Nonce32 = Nonce32 ByteString |
1038 | { announcePingId :: NodeId -- Ping ID | 1088 | deriving (Eq, Ord, ByteArrayAccess, Data) |
1039 | , announceSeeking :: NodeId -- Public key we are searching for | 1089 | |
1040 | , announceKey :: NodeId -- Public key that we want those sending back data packets to use | 1090 | instance S.Serialize Nonce32 where |
1091 | get = Nonce32 <$> S.getBytes 32 | ||
1092 | put (Nonce32 bs) = S.putByteString bs | ||
1093 | |||
1094 | data AnnounceRequest = AnnounceRequest | ||
1095 | { announcePingId :: Nonce32 -- Ping ID | ||
1096 | , announceSeeking :: NodeId -- Public key we are searching for | ||
1097 | , announceKey :: NodeId -- Public key that we want those sending back data packets to use | ||
1098 | } | ||
1099 | |||
1100 | instance S.Serialize AnnounceRequest where | ||
1101 | get = AnnounceRequest <$> S.get <*> S.get <*> S.get | ||
1102 | put (AnnounceRequest p s k) = S.put (p,s,k) | ||
1103 | |||
1104 | data KeyRecord = NotStored Nonce32 | ||
1105 | | SendBackKey Tox.PubKey | ||
1106 | | Acknowledged Nonce32 | ||
1107 | |||
1108 | instance S.Serialize KeyRecord where | ||
1109 | get = do | ||
1110 | is_stored <- S.get :: S.Get Word8 | ||
1111 | case is_stored of | ||
1112 | 1 -> SendBackKey <$> S.get | ||
1113 | 2 -> Acknowledged <$> S.get | ||
1114 | _ -> NotStored <$> S.get | ||
1115 | put (NotStored n32) = S.put (0 :: Word8) >> S.put n32 | ||
1116 | put (SendBackKey key) = S.put (1 :: Word8) >> S.put key | ||
1117 | put (Acknowledged n32) = S.put (2 :: Word8) >> S.put n32 | ||
1118 | |||
1119 | data AnnounceResponse = AnnounceResponse | ||
1120 | { is_stored :: KeyRecord | ||
1121 | , announceNodes :: SendNodes | ||
1041 | } | 1122 | } |
1042 | 1123 | ||
1124 | instance S.Serialize AnnounceResponse where | ||
1125 | get = AnnounceResponse <$> S.get <*> S.get | ||
1126 | put (AnnounceResponse st ns) = S.put st >> S.put ns | ||
1127 | |||
1043 | pingH :: NodeInfo -> Ping -> IO Pong | 1128 | pingH :: NodeInfo -> Ping -> IO Pong |
1044 | pingH _ Ping = return Pong | 1129 | pingH _ Ping = return Pong |
1045 | 1130 | ||
@@ -1075,6 +1160,50 @@ getNodesH routing addr (GetNodes nid) = do | |||
1075 | 1160 | ||
1076 | k = 4 | 1161 | k = 4 |
1077 | 1162 | ||
1163 | -- Toxcore generates `ping_id`s by taking a 32 byte sha hash of the current time, | ||
1164 | -- some secret bytes generated when the instance is created, the current time | ||
1165 | -- divided by a 20 second timeout, the public key of the requester and the source | ||
1166 | -- ip/port that the packet was received from. Since the ip/port that the packet | ||
1167 | -- was received from is in the `ping_id`, the announce packets being sent with a | ||
1168 | -- ping id must be sent using the same path as the packet that we received the | ||
1169 | -- `ping_id` from or announcing will fail. | ||
1170 | -- | ||
1171 | -- The reason for this 20 second timeout in toxcore is that it gives a reasonable | ||
1172 | -- time (20 to 40 seconds) for a peer to announce himself while taking in count | ||
1173 | -- all the possible delays with some extra seconds. | ||
1174 | announceH :: Routing -> TVar SessionTokens -> TVar AnnouncedKeys -> NodeInfo -> AnnounceRequest -> IO AnnounceResponse | ||
1175 | announceH routing toks keydb naddr req = do | ||
1176 | case () of | ||
1177 | _ | announcePingId req == zeros32 | ||
1178 | -> go False | ||
1179 | |||
1180 | _ | Nonce32 bs <- announcePingId req | ||
1181 | , let tok = fromPaddedByteString 32 bs | ||
1182 | -> checkToken toks naddr tok >>= go | ||
1183 | where | ||
1184 | go withTok = do | ||
1185 | ns <- getNodesH routing naddr (GetNodes (announceSeeking req)) | ||
1186 | tm <- getPOSIXTime | ||
1187 | let storing = (nodeId naddr == announceSeeking req) | ||
1188 | record <- atomically $ do | ||
1189 | when (withTok && storing) $ do | ||
1190 | let ni = Tox.Aliased (naddr { nodeId = announceKey req }) | ||
1191 | -- Note: The following distance calculation assumes that | ||
1192 | -- our nodeid doesn't change and is the same for both | ||
1193 | -- routing4 and routing6. | ||
1194 | d = xor (nodeId (tentativeId routing)) | ||
1195 | (announceSeeking req) | ||
1196 | modifyTVar' keydb (insertKey tm (announceSeeking req) ni d) | ||
1197 | ks <- readTVar keydb | ||
1198 | return $ snd <$> MinMaxPSQ.lookup' (announceSeeking req) (keyAssoc ks) | ||
1199 | newtok <- if storing | ||
1200 | then Nonce32 . toPaddedByteString 32 <$> grantToken toks naddr | ||
1201 | else return $ zeros32 | ||
1202 | let k = case record of | ||
1203 | Nothing -> NotStored newtok | ||
1204 | Just (Tox.Aliased ni) | storing -> Acknowledged newtok | ||
1205 | Just (Tox.Aliased ni) -> SendBackKey (nodeId ni) | ||
1206 | return $ AnnounceResponse k ns | ||
1078 | 1207 | ||
1079 | {- | 1208 | {- |
1080 | symmetricCipher :: DRG g => STM ByteString -> STM g -> (g -> STM ()) -> ByteString -> IO (Tox.Nonce24, SymmetricCiphered) | 1209 | symmetricCipher :: DRG g => STM ByteString -> STM g -> (g -> STM ()) -> ByteString -> IO (Tox.Nonce24, SymmetricCiphered) |
@@ -1157,9 +1286,9 @@ onionResponse1H symdecipher udp addr Message{ msgNonce | |||
1157 | -} | 1286 | -} |
1158 | 1287 | ||
1159 | intKey :: TransactionId -> Int | 1288 | intKey :: TransactionId -> Int |
1160 | intKey (TransactionId (Nonce8 w) _) = fromIntegral w | 1289 | intKey (TransactionId (Tox.Nonce8 w) _) = fromIntegral w |
1161 | 1290 | ||
1162 | nonceKey :: TransactionId -> Nonce8 | 1291 | nonceKey :: TransactionId -> Tox.Nonce8 |
1163 | nonceKey (TransactionId n _) = n | 1292 | nonceKey (TransactionId n _) = n |
1164 | 1293 | ||
1165 | -- randomBytesGenerate :: ByteArray byteArray => Int -> gen -> (byteArray, gen) | 1294 | -- randomBytesGenerate :: ByteArray byteArray => Int -> gen -> (byteArray, gen) |
@@ -1168,7 +1297,7 @@ gen :: forall gen. DRG gen => gen -> (TransactionId, gen) | |||
1168 | gen g = let (bs, g') = randomBytesGenerate 24 g | 1297 | gen g = let (bs, g') = randomBytesGenerate 24 g |
1169 | (ws, g'') = randomBytesGenerate 8 g' | 1298 | (ws, g'') = randomBytesGenerate 8 g' |
1170 | Right w = S.runGet S.getWord64be ws | 1299 | Right w = S.runGet S.getWord64be ws |
1171 | in ( TransactionId (Nonce8 w) (Tox.Nonce24 bs), g'' ) | 1300 | in ( TransactionId (Tox.Nonce8 w) (Tox.Nonce24 bs), g'' ) |
1172 | 1301 | ||
1173 | 1302 | ||
1174 | 1303 | ||
@@ -1206,3 +1335,16 @@ toxSearch qry = Search | |||
1206 | 1335 | ||
1207 | nodeSearch client = toxSearch (getNodes client) | 1336 | nodeSearch client = toxSearch (getNodes client) |
1208 | 1337 | ||
1338 | |||
1339 | type NodeDistance = Tox.PubKey | ||
1340 | |||
1341 | data AnnouncedKeys = AnnouncedKeys | ||
1342 | { keyByAge :: PSQ NodeId (Down POSIXTime) -- timeout of 300 seconds | ||
1343 | , keyAssoc :: MinMaxPSQ' Tox.PubKey NodeDistance (Tox.Aliased NodeInfo) | ||
1344 | } | ||
1345 | |||
1346 | insertKey :: POSIXTime -> Tox.PubKey -> Tox.Aliased NodeInfo -> NodeDistance -> AnnouncedKeys -> AnnouncedKeys | ||
1347 | insertKey tm pub ni d keydb = AnnouncedKeys | ||
1348 | { keyByAge = PSQ.insert pub (Down tm) (keyByAge keydb) | ||
1349 | , keyAssoc = MinMaxPSQ.insert' pub ni d (keyAssoc keydb) | ||
1350 | } | ||