summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--Tox.hs172
1 files changed, 140 insertions, 32 deletions
diff --git a/Tox.hs b/Tox.hs
index 4df329d3..6969e652 100644
--- a/Tox.hs
+++ b/Tox.hs
@@ -43,7 +43,8 @@ import Foreign.Ptr
43import Foreign.Storable 43import Foreign.Storable
44import GHC.Generics (Generic) 44import GHC.Generics (Generic)
45import Network.Address (Address, fromSockAddr, sockAddrPort, testIdBit, 45import Network.Address (Address, fromSockAddr, sockAddrPort, testIdBit,
46 toSockAddr, setPort, un4map, WantIP(..), ipFamily) 46 toSockAddr, setPort, un4map, WantIP(..), ipFamily,
47 either4or6)
47import Network.QueryResponse 48import Network.QueryResponse
48import Network.Socket 49import Network.Socket
49import System.Endian 50import System.Endian
@@ -65,6 +66,7 @@ import Control.Monad
65import Text.Read 66import Text.Read
66import Kademlia 67import Kademlia
67import Network.BitTorrent.DHT.Search (Search (..)) 68import Network.BitTorrent.DHT.Search (Search (..))
69import Text.Printf
68 70
69newtype NodeId = NodeId ByteString 71newtype NodeId = NodeId ByteString
70 deriving (Eq,Ord,ByteArrayAccess, Bits, Hashable) 72 deriving (Eq,Ord,ByteArrayAccess, Bits, Hashable)
@@ -109,7 +111,7 @@ instance ToJSON NodeInfo where
109 , "port" .= (fromIntegral port :: Int) 111 , "port" .= (fromIntegral port :: Int)
110 ] 112 ]
111 | otherwise 113 | otherwise
112 = JSON.object [ "node-id" .= show nid 114 = JSON.object [ "public_key" .= show nid
113 , "ipv6" .= show ip6 115 , "ipv6" .= show ip6
114 , "port" .= (fromIntegral port :: Int) 116 , "port" .= (fromIntegral port :: Int)
115 ] 117 ]
@@ -215,13 +217,47 @@ data TransactionId = TransactionId
215 , cryptoNonce :: Nonce24 -- ^ Used during the encryption layer. 217 , cryptoNonce :: Nonce24 -- ^ Used during the encryption layer.
216 } 218 }
217 219
220-- https://toktok.ltd/spec#packet-kind
221-- calls this "Packet Kind"
218newtype Method = MessageType Word8 222newtype Method = MessageType Word8
219 deriving (Eq, Ord, S.Serialize) 223 deriving (Eq, Ord, S.Serialize)
220 224
221pattern PingType = MessageType 0 225pattern PingType = MessageType 0 -- 0x00 Ping Request
222pattern PongType = MessageType 1 226pattern PongType = MessageType 1 -- 0x01 Ping Response
223pattern GetNodesType = MessageType 2 227pattern GetNodesType = MessageType 2 -- 0x02 Nodes Request
224pattern SendNodesType = MessageType 4 228pattern SendNodesType = MessageType 4 -- 0x04 Nodes Response
229-- 0x18 Cookie Request
230-- 0x19 Cookie Response
231-- 0x1a Crypto Handshake
232-- 0x1b Crypto Data
233
234-- TODO: Auth fail:
235pattern DHTRequestType = MessageType 32 -- 0x20 DHT Request
236
237-- 0x21 LAN Discovery
238
239-- TODO: Auth fail:
240pattern OnionRequest0 = MessageType 128 -- 0x80 Onion Request 0
241pattern OnionRequest1 = MessageType 129 -- 0x81 Onion Request 1
242pattern OnionRequest2 = MessageType 130 -- 0x82 Onion Request 2
243pattern AnnounceType = MessageType 131 -- 0x83 Announce Request
244
245-- 0x84 Announce Response
246-- 0x85 Onion Data Request
247-- 0x86 Onion Data Response
248-- 0x8c Onion Response 3
249-- 0x8d Onion Response 2
250-- 0x8e Onion Response 1
251-- 0xf0 Bootstrap Info
252
253-- TODO Fix these fails...
254-- GetNodesType decipherAndAuth: auth fail
255-- MessageType 128 decipherAndAuth: auth fail
256-- MessageType 129 decipherAndAuth: auth fail
257-- MessageType 130 decipherAndAuth: auth fail
258-- MessageType 131 decipherAndAuth: auth fail
259-- MessageType 32 decipherAndAuth: auth fail
260
225 261
226instance Show Method where 262instance Show Method where
227 showsPrec d PingType = mappend "PingType" 263 showsPrec d PingType = mappend "PingType"
@@ -275,8 +311,13 @@ data Ciphered = Ciphered { cipheredMAC :: Poly1305.Auth
275getMessage :: S.Get (Message Ciphered) 311getMessage :: S.Get (Message Ciphered)
276getMessage = do 312getMessage = do
277 typ <- S.get 313 typ <- S.get
278 nid <- S.get 314 (nid,tid) <- case typ of -- Seriously... what the fuck?
279 tid <- S.get 315 DHTRequestType -> flip (,) <$> S.get <*> S.get
316 OnionRequest0 -> flip (,) <$> S.get <*> S.get
317 OnionRequest1 -> flip (,) <$> S.get <*> S.get
318 -- OnionRequest2 -> flip (,) <$> S.get <*> S.get
319 AnnounceType -> flip (,) <$> S.get <*> S.get
320 _ -> (,) <$> S.get <*> S.get
280 mac <- Poly1305.Auth . BA.convert <$> S.getBytes 16 321 mac <- Poly1305.Auth . BA.convert <$> S.getBytes 16
281 cnt <- S.remaining 322 cnt <- S.remaining
282 bs <- S.getBytes cnt 323 bs <- S.getBytes cnt
@@ -288,8 +329,13 @@ getMessage = do
288putMessage :: Message Ciphered -> S.Put 329putMessage :: Message Ciphered -> S.Put
289putMessage (Message {..}) = do 330putMessage (Message {..}) = do
290 S.put msgType 331 S.put msgType
291 S.put msgOrigin 332 case msgType of -- Seriously... what the fuck?
292 S.put msgNonce 333 DHTRequestType -> S.put msgNonce >> S.put msgOrigin
334 OnionRequest0 -> S.put msgNonce >> S.put msgOrigin
335 OnionRequest1 -> S.put msgNonce >> S.put msgOrigin
336 -- OnionRequest2 -> S.put msgNonce >> S.put msgOrigin
337 AnnounceType -> S.put msgNonce >> S.put msgOrigin
338 _ -> S.put msgOrigin >> S.put msgNonce
293 let Ciphered (Poly1305.Auth mac) bs = msgPayload 339 let Ciphered (Poly1305.Auth mac) bs = msgPayload
294 S.putByteString (BA.convert mac) 340 S.putByteString (BA.convert mac)
295 S.putByteString bs 341 S.putByteString bs
@@ -365,6 +411,8 @@ withSecret f sk recipient nonce x = f hash crypt x
365 (hash, crypt) = computeSharedSecret sk recipient nonce 411 (hash, crypt) = computeSharedSecret sk recipient nonce
366 412
367 413
414-- Encrypt-then-Mac: Encrypt the cleartext, then compute the MAC on the
415-- ciphertext, and prepend it to the ciphertext
368encipherAndHash :: Poly1305.State -> XSalsa.State -> ByteString -> Ciphered 416encipherAndHash :: Poly1305.State -> XSalsa.State -> ByteString -> Ciphered
369encipherAndHash hash crypt m = Ciphered a c 417encipherAndHash hash crypt m = Ciphered a c
370 where 418 where
@@ -379,6 +427,30 @@ decipherAndAuth hash crypt (Ciphered mac c)
379 m = fst . XSalsa.combine crypt $ c 427 m = fst . XSalsa.combine crypt $ c
380 a = Poly1305.finalize . Poly1305.update hash $ c 428 a = Poly1305.finalize . Poly1305.update hash $ c
381 429
430nibble :: Word8 -> Char
431nibble b = intToDigit (fromIntegral (b .&. 0x0F))
432
433xxd :: Int -> ByteString -> [String]
434xxd offset bs | B.null bs = []
435xxd offset bs = printf "%03x: %s" offset ds : xxd (offset + B.length xs) bs'
436 where
437 ds = unwords $ map (\byte -> [nibble (byte `shiftR` 4), nibble byte])
438 $ B.unpack xs
439 (xs,bs') = B.splitAt 16 bs
440
441showPayloadError ciphered naddr flow err = unlines (map (prefix ++) xs)
442 where
443 xs = unwords [show (msgType ciphered), err]
444 : xxd 0 (BA.convert mac <> ciphertext)
445
446 Message { msgPayload = Ciphered (Poly1305.Auth mac) ciphertext } = ciphered
447
448 prefix = show naddr <> flow
449
450
451showParseError bs addr err = unlines $
452 concat [ either show show (either4or6 addr), " --> ", err ]
453 : xxd 0 bs
382 454
383-- TODO: 455-- TODO:
384-- Represents the encrypted portion of a Tox packet. 456-- Represents the encrypted portion of a Tox packet.
@@ -387,10 +459,12 @@ decipherAndAuth hash crypt (Ciphered mac c)
387-- Generic packet type: Message (Payload ByteString) 459-- Generic packet type: Message (Payload ByteString)
388 460
389parsePacket :: SecretKey -> SecretsCache -> ByteString -> SockAddr -> Either String (Message ByteString, NodeInfo) 461parsePacket :: SecretKey -> SecretsCache -> ByteString -> SockAddr -> Either String (Message ByteString, NodeInfo)
390parsePacket sk cache bs addr = do ciphered <- S.runGet getMessage bs 462parsePacket sk cache bs addr = left (showParseError bs addr) $ do
391 msg <- decryptMessage sk cache ciphered 463 ciphered <- S.runGet getMessage bs
392 ni <- nodeInfo (msgOrigin msg) addr 464 ni <- nodeInfo (msgOrigin ciphered) addr
393 return (msg, ni) 465 left (showPayloadError ciphered ni " --> ") $ do
466 msg <- decryptMessage sk cache ciphered
467 return (msg, ni)
394 468
395encodePacket :: SecretKey -> SecretsCache -> Message ByteString -> NodeInfo -> (ByteString, SockAddr) 469encodePacket :: SecretKey -> SecretsCache -> Message ByteString -> NodeInfo -> (ByteString, SockAddr)
396encodePacket sk cache msg ni = ( S.runPut . putMessage $ encryptMessage sk cache (nodeId ni) msg 470encodePacket sk cache msg ni = ( S.runPut . putMessage $ encryptMessage sk cache (nodeId ni) msg
@@ -416,20 +490,23 @@ newClient addr = do
416 let pubkey = key2id $ toPublic secret 490 let pubkey = key2id $ toPublic secret
417 cache <- newEmptyCache 491 cache <- newEmptyCache
418 drg <- getSystemDRG 492 drg <- getSystemDRG
419 let tentative_info = NodeInfo 493 let tentative_ip4 = fromMaybe (IPv4 $ toEnum 0) (IPv4 <$> fromSockAddr addr)
494 tentative_ip6 = fromMaybe (IPv6 $ toEnum 0) (IPv6 <$> fromSockAddr addr)
495 tentative_info = NodeInfo
420 { nodeId = pubkey 496 { nodeId = pubkey
421 , nodeIP = fromMaybe (toEnum 0) $ fromSockAddr addr 497 , nodeIP = fromMaybe (toEnum 0) (fromSockAddr addr)
422 , nodePort = fromMaybe 0 $ sockAddrPort addr 498 , nodePort = fromMaybe 0 $ sockAddrPort addr
423 } 499 }
500 tentative_info4 = tentative_info { nodeIP = tentative_ip4 }
424 tentative_info6 <- 501 tentative_info6 <-
425 maybe tentative_info 502 maybe (tentative_info { nodeIP = tentative_ip6 })
426 (\ip6 -> tentative_info { nodeIP = IPv6 ip6 }) 503 (\ip6 -> tentative_info { nodeIP = IPv6 ip6 })
427 <$> global6 504 <$> global6
428 addr4 <- atomically $ newTChan 505 addr4 <- atomically $ newTChan
429 addr6 <- atomically $ newTChan 506 addr6 <- atomically $ newTChan
430 routing <- atomically $ do 507 routing <- atomically $ do
431 let nobkts = R.defaultBucketCount :: Int 508 let nobkts = R.defaultBucketCount :: Int
432 tbl4 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info nobkts 509 tbl4 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info4 nobkts
433 tbl6 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info6 nobkts 510 tbl6 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info6 nobkts
434 let updateIPVote tblvar addrvar a = do 511 let updateIPVote tblvar addrvar a = do
435 bkts <- readTVar tblvar 512 bkts <- readTVar tblvar
@@ -457,6 +534,7 @@ newClient addr = do
457 map_var <- atomically $ newTVar (drg, mempty) 534 map_var <- atomically $ newTVar (drg, mempty)
458 return $ Left (mapT,map_var) 535 return $ Left (mapT,map_var)
459 let net = onInbound (updateRouting outgoingClient routing) 536 let net = onInbound (updateRouting outgoingClient routing)
537 $ addVerbosity
460 $ layerTransport (parsePacket secret cache) 538 $ layerTransport (parsePacket secret cache)
461 (encodePacket secret cache) 539 (encodePacket secret cache)
462 $ udp 540 $ udp
@@ -477,6 +555,10 @@ newClient addr = do
477 handlers PingType = handler PongType pingH 555 handlers PingType = handler PongType pingH
478 handlers GetNodesType = handler SendNodesType $ getNodesH routing 556 handlers GetNodesType = handler SendNodesType $ getNodesH routing
479 handlers _ = Nothing 557 handlers _ = Nothing
558 -- TODO DHTRequest public key (onion)
559 -- TODO DHTRequest NAT ping
560 -- TODO BootstrapInfo 0xf0
561 --
480 562
481 genNonce24 var (TransactionId nonce8 _) = atomically $ do 563 genNonce24 var (TransactionId nonce8 _) = atomically $ do
482 (g,pending) <- readTVar var 564 (g,pending) <- readTVar var
@@ -545,16 +627,36 @@ dropEnd8 :: ByteString -> ByteString
545dropEnd8 bs = B.take (B.length bs - 8) bs 627dropEnd8 bs = B.take (B.length bs - 8) bs
546 628
547 629
630-- Add detailed printouts for every packet.
631addVerbosity tr =
632 tr { awaitMessage = do
633 m <- awaitMessage tr
634 forM_ m $ mapM_ $ \(msg,addr) -> do
635 hPutStrLn stderr ( (show addr)
636 ++ " --> " ++ show (msgType msg))
637 return m
638 , sendMessage = \addr msg -> do
639 hPutStrLn stderr ( (show addr)
640 ++ " <-- " ++ show (msgType msg))
641 sendMessage tr addr msg
642 }
643
548classify :: Message ByteString -> MessageClass String Method TransactionId 644classify :: Message ByteString -> MessageClass String Method TransactionId
549classify (Message { msgType = typ 645classify (Message { msgType = typ
550 , msgPayload = bs 646 , msgPayload = bs
551 , msgNonce = nonce24 }) = go $ TransactionId (last8 bs) nonce24 647 , msgNonce = nonce24 }) = go $ TransactionId (last8 bs) nonce24
552 where 648 where
553 go = case typ of 649 go = case typ of
554 PingType -> IsQuery PingType 650 PingType -> IsQuery typ
555 GetNodesType -> IsQuery GetNodesType 651 GetNodesType -> IsQuery typ
556 PongType -> IsResponse 652 PongType -> IsResponse
557 SendNodesType -> IsResponse 653 SendNodesType -> IsResponse
654 DHTRequestType -> IsQuery typ
655 OnionRequest0 -> IsQuery typ
656 OnionRequest1 -> IsQuery typ
657 OnionRequest2 -> IsQuery typ
658 AnnounceType -> IsQuery typ
659 _ -> const $ IsUnknown ("Unknown message type: "++show typ)
558 660
559encodePayload typ (TransactionId (Nonce8 tid) nonce) self dest b 661encodePayload typ (TransactionId (Nonce8 tid) nonce) self dest b
560 = Message { msgType = typ 662 = Message { msgType = typ
@@ -631,6 +733,12 @@ pingH _ Ping = return Pong
631prefer4or6 :: NodeInfo -> Maybe WantIP -> WantIP 733prefer4or6 :: NodeInfo -> Maybe WantIP -> WantIP
632prefer4or6 addr iptyp = fromMaybe (ipFamily $ nodeIP addr) iptyp 734prefer4or6 addr iptyp = fromMaybe (ipFamily $ nodeIP addr) iptyp
633 735
736-- TODO: This should cover more cases
737isLocal (IPv6 ip6) = (ip6 == toEnum 0)
738isLocal (IPv4 ip4) = (ip4 == toEnum 0)
739
740isGlobal = not . isLocal
741
634getNodesH :: Routing -> NodeInfo -> GetNodes -> IO SendNodes 742getNodesH :: Routing -> NodeInfo -> GetNodes -> IO SendNodes
635getNodesH routing addr (GetNodes nid) = do 743getNodesH routing addr (GetNodes nid) = do
636 let preferred = prefer4or6 addr Nothing 744 let preferred = prefer4or6 addr Nothing
@@ -639,13 +747,16 @@ getNodesH routing addr (GetNodes nid) = do
639 ni4 <- R.thisNode <$> readTVar (routing4 routing) 747 ni4 <- R.thisNode <$> readTVar (routing4 routing)
640 ni6 <- R.thisNode <$> readTVar (routing6 routing) 748 ni6 <- R.thisNode <$> readTVar (routing6 routing)
641 return $ case ipFamily (nodeIP addr) of 749 return $ case ipFamily (nodeIP addr) of
642 Want_IP4 -> (id, (++ [ni6])) 750 Want_IP4 | isGlobal (nodeIP ni6) -> (id, (++ [ni6]))
643 Want_IP6 -> ((++ [ni4]), id) 751 Want_IP6 | isGlobal (nodeIP ni4) -> ((++ [ni4]), id)
644 ks <- bool (return []) (go append4 $ routing4 routing) (preferred /= Want_IP6) 752 _ -> (id, id)
645 ks6 <- bool (return []) (go append6 $ routing6 routing) (preferred /= Want_IP4) 753 ks <- go append4 $ routing4 routing
646 return $ case preferred of 754 ks6 <- go append6 $ routing6 routing
647 Want_IP6 -> SendNodes (take 4 $ ks6 ++ ks) 755 let (ns1,ns2) = case preferred of Want_IP6 -> (ks6,ks)
648 Want_IP4 -> SendNodes (take 4 $ ks ++ ks6) 756 Want_IP4 -> (ks,ks6)
757 return $ SendNodes
758 $ if null ns2 then ns1
759 else take 4 (take 3 ns1 ++ ns2)
649 where 760 where
650 go f var = f . R.kclosest toxSpace k nid <$> atomically (readTVar var) 761 go f var = f . R.kclosest toxSpace k nid <$> atomically (readTVar var)
651 762
@@ -671,9 +782,6 @@ toxSend meth unwrap msg client nid addr = do
671 -- sendQuery will return (Just (Left _)) on a parse error. We're going to 782 -- sendQuery will return (Just (Left _)) on a parse error. We're going to
672 -- blow it away with the join-either sequence. 783 -- blow it away with the join-either sequence.
673 -- TODO: Do something with parse errors. 784 -- TODO: Do something with parse errors.
674 -- "Failed reading: Malformed ping.\nEmpty call stack\n"
675 -- "Failed reading: unsupported address family\nEmpty call stack\n"
676 either print (const $ return ()) $ fromMaybe (Left "Nothing") reply
677 return $ join $ either (const Nothing) Just <$> reply 785 return $ join $ either (const Nothing) Just <$> reply
678 where 786 where
679 serializer = MethodSerializer 787 serializer = MethodSerializer