diff options
author | joe <joe@jerkface.net> | 2017-07-29 00:58:52 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-07-29 01:03:35 -0400 |
commit | f876da224f503542394b3d7614fcc161106ebbb4 (patch) | |
tree | 411d1c94ac482a94dcaeb6ff17175673bce0939b | |
parent | d0ff6c3ac977035f3493b679978da73517550028 (diff) |
Detect a global ipv6 address via "ip" command.
-rw-r--r-- | Global6.hs | 28 | ||||
-rw-r--r-- | Kademlia.hs | 8 | ||||
-rw-r--r-- | Mainline.hs | 50 | ||||
-rw-r--r-- | bittorrent.cabal | 2 |
4 files changed, 68 insertions, 20 deletions
diff --git a/Global6.hs b/Global6.hs new file mode 100644 index 00000000..346be708 --- /dev/null +++ b/Global6.hs | |||
@@ -0,0 +1,28 @@ | |||
1 | module Global6 where | ||
2 | |||
3 | import Control.Monad | ||
4 | import Data.IP | ||
5 | import Data.List | ||
6 | import Data.Maybe | ||
7 | import Network.Socket | ||
8 | import System.Process | ||
9 | import Text.Read | ||
10 | |||
11 | parseIpAddr :: String -> Maybe IPv6 | ||
12 | parseIpAddr s = do | ||
13 | let ws = words s | ||
14 | (addr,bs) = splitAt 1 $ drop 1 $ dropWhile (/= "inet6") ws | ||
15 | guard ("global" `elem` bs) | ||
16 | addr <- listToMaybe addr | ||
17 | guard (not $ isPrefixOf "fd" addr) | ||
18 | guard (not $ isPrefixOf "fc" addr) | ||
19 | let (addr',slash) = break (=='/') addr | ||
20 | ip6 <- readMaybe addr' | ||
21 | return $ (ip6 :: IPv6) | ||
22 | |||
23 | |||
24 | global6 :: IO (Maybe IPv6) | ||
25 | global6 = do | ||
26 | addrs <- lines <$> readProcess "ip" ["-o","-6","addr"] "" | ||
27 | return $ foldr1 mplus $ map parseIpAddr addrs | ||
28 | |||
diff --git a/Kademlia.hs b/Kademlia.hs index ef5c6a48..017209a7 100644 --- a/Kademlia.hs +++ b/Kademlia.hs | |||
@@ -267,10 +267,11 @@ forkPollForRefresh interval psq refresh = do | |||
267 | 267 | ||
268 | refreshBucket :: forall nid tok ni addr. | 268 | refreshBucket :: forall nid tok ni addr. |
269 | ( Show nid, FiniteBits nid, Serialize nid, Ord nid, Ord ni, Hashable nid, Hashable ni, Ord addr ) => | 269 | ( Show nid, FiniteBits nid, Serialize nid, Ord nid, Ord ni, Hashable nid, Hashable ni, Ord addr ) => |
270 | Search nid addr tok ni ni -> TVar (BucketList ni) -> nid -> Int -> IO Int | 270 | Search nid addr tok ni ni -> TVar (BucketList ni) -> Int -> IO Int |
271 | refreshBucket sch var nid n = do | 271 | refreshBucket sch var n = do |
272 | tbl <- atomically (readTVar var) | 272 | tbl <- atomically (readTVar var) |
273 | let count = bktCount tbl | 273 | let count = bktCount tbl |
274 | nid = kademliaLocation (searchSpace sch) (thisNode tbl) | ||
274 | sample <- if n+1 >= count -- Is this the last bucket? | 275 | sample <- if n+1 >= count -- Is this the last bucket? |
275 | then return nid -- Yes? Search our own id. | 276 | then return nid -- Yes? Search our own id. |
276 | else genBucketSample nid -- No? Generate a random id. | 277 | else genBucketSample nid -- No? Generate a random id. |
@@ -362,7 +363,6 @@ bootstrap sch var ping ns ns0 = do | |||
362 | hPutStrLn stderr | 363 | hPutStrLn stderr |
363 | $ "Not enough buckets, refresh " ++ show (R.defaultBucketCount - 1) | 364 | $ "Not enough buckets, refresh " ++ show (R.defaultBucketCount - 1) |
364 | cnt <- refreshBucket sch var | 365 | cnt <- refreshBucket sch var |
365 | (kademliaLocation (searchSpace sch) (thisNode tbl)) | ||
366 | (R.defaultBucketCount - 1) | 366 | (R.defaultBucketCount - 1) |
367 | again cnt | 367 | again cnt |
368 | (size,num):_ -> do | 368 | (size,num):_ -> do |
@@ -371,5 +371,5 @@ bootstrap sch var ping ns ns0 = do | |||
371 | let num' | bktCount tbl < R.defaultBucketCount = R.defaultBucketCount - 1 | 371 | let num' | bktCount tbl < R.defaultBucketCount = R.defaultBucketCount - 1 |
372 | | otherwise = num | 372 | | otherwise = num |
373 | hPutStrLn stderr $ "Bucket too small, refresh "++ show (num',(size,num),shp) | 373 | hPutStrLn stderr $ "Bucket too small, refresh "++ show (num',(size,num),shp) |
374 | cnt <- refreshBucket sch var (kademliaLocation (searchSpace sch) (thisNode tbl)) num' | 374 | cnt <- refreshBucket sch var num' |
375 | again cnt | 375 | again cnt |
diff --git a/Mainline.hs b/Mainline.hs index deb75079..6aa1c517 100644 --- a/Mainline.hs +++ b/Mainline.hs | |||
@@ -77,6 +77,7 @@ import Control.Exception (SomeException (..), handle) | |||
77 | import qualified Data.Aeson as JSON | 77 | import qualified Data.Aeson as JSON |
78 | ;import Data.Aeson (FromJSON, ToJSON, (.=)) | 78 | ;import Data.Aeson (FromJSON, ToJSON, (.=)) |
79 | import Text.Read | 79 | import Text.Read |
80 | import Global6 | ||
80 | 81 | ||
81 | newtype NodeId = NodeId ByteString | 82 | newtype NodeId = NodeId ByteString |
82 | deriving (Eq,Ord,ByteArrayAccess, Bits, Hashable) | 83 | deriving (Eq,Ord,ByteArrayAccess, Bits, Hashable) |
@@ -524,17 +525,24 @@ newClient :: SockAddr -> IO (MainlineClient, Routing, SwarmsDatabase) | |||
524 | newClient addr = do | 525 | newClient addr = do |
525 | udp <- udpTransport addr | 526 | udp <- udpTransport addr |
526 | nid <- NodeId <$> getRandomBytes 20 | 527 | nid <- NodeId <$> getRandomBytes 20 |
527 | let tenative_info = NodeInfo | 528 | let tentative_info = NodeInfo |
528 | { nodeId = nid | 529 | { nodeId = nid |
529 | , nodeIP = fromMaybe (toEnum 0) $ fromSockAddr addr | 530 | , nodeIP = fromMaybe (toEnum 0) $ fromSockAddr addr |
530 | , nodePort = fromMaybe 0 $ sockAddrPort addr | 531 | , nodePort = fromMaybe 0 $ sockAddrPort addr |
531 | } | 532 | } |
533 | tentative_info6 <- | ||
534 | maybe tentative_info | ||
535 | (\ip6 -> tentative_info { nodeId = fromMaybe (nodeId tentative_info) | ||
536 | $ bep42 (toSockAddr ip6) (nodeId tentative_info) | ||
537 | , nodeIP = IPv6 ip6 | ||
538 | }) | ||
539 | <$> global6 | ||
532 | addr4 <- atomically $ newTChan | 540 | addr4 <- atomically $ newTChan |
533 | addr6 <- atomically $ newTChan | 541 | addr6 <- atomically $ newTChan |
534 | routing <- atomically $ do | 542 | routing <- atomically $ do |
535 | let nobkts = R.defaultBucketCount :: Int | 543 | let nobkts = R.defaultBucketCount :: Int |
536 | tbl4 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tenative_info nobkts | 544 | tbl4 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info nobkts |
537 | tbl6 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tenative_info nobkts | 545 | tbl6 <- newTVar $ R.nullTable (comparing nodeId) (\s -> hashWithSalt s . nodeId) tentative_info6 nobkts |
538 | let updateIPVote tblvar addrvar a = do | 546 | let updateIPVote tblvar addrvar a = do |
539 | bkts <- readTVar tblvar | 547 | bkts <- readTVar tblvar |
540 | case bep42 a (nodeId $ R.thisNode bkts) of | 548 | case bep42 a (nodeId $ R.thisNode bkts) of |
@@ -552,7 +560,7 @@ newClient addr = do | |||
552 | committee6 <- newTriadCommittee $ updateIPVote tbl6 addr6 | 560 | committee6 <- newTriadCommittee $ updateIPVote tbl6 addr6 |
553 | sched4 <- newTVar Int.empty | 561 | sched4 <- newTVar Int.empty |
554 | sched6 <- newTVar Int.empty | 562 | sched6 <- newTVar Int.empty |
555 | return $ Routing tenative_info sched4 tbl4 committee4 sched6 tbl6 committee6 | 563 | return $ Routing tentative_info sched4 tbl4 committee4 sched6 tbl6 committee6 |
556 | swarms <- newSwarmsDatabase | 564 | swarms <- newSwarmsDatabase |
557 | map_var <- atomically $ newTVar (0, mempty) | 565 | map_var <- atomically $ newTVar (0, mempty) |
558 | let net = onInbound (updateRouting outgoingClient routing) | 566 | let net = onInbound (updateRouting outgoingClient routing) |
@@ -619,11 +627,11 @@ newClient addr = do | |||
619 | refresh_thread4 <- forkPollForRefresh | 627 | refresh_thread4 <- forkPollForRefresh |
620 | (15*60) | 628 | (15*60) |
621 | (sched4 routing) | 629 | (sched4 routing) |
622 | (refreshBucket (nodeSearch client) (routing4 routing) (nodeId tenative_info)) | 630 | (refreshBucket (nodeSearch client) (routing4 routing)) |
623 | refresh_thread6 <- forkPollForRefresh | 631 | refresh_thread6 <- forkPollForRefresh |
624 | (15*60) | 632 | (15*60) |
625 | (sched6 routing) | 633 | (sched6 routing) |
626 | (refreshBucket (nodeSearch client) (routing6 routing) (nodeId tenative_info)) | 634 | (refreshBucket (nodeSearch client) (routing6 routing)) |
627 | 635 | ||
628 | return (client, routing, swarms) | 636 | return (client, routing, swarms) |
629 | 637 | ||
@@ -705,13 +713,15 @@ updateRouting client routing naddr msg = do | |||
705 | Want_IP6 -> go (routing6 routing) (committee6 routing) (sched6 routing) | 713 | Want_IP6 -> go (routing6 routing) (committee6 routing) (sched6 routing) |
706 | where | 714 | where |
707 | go tbl committee sched = do | 715 | go tbl committee sched = do |
708 | case msg of | 716 | self <- atomically $ R.thisNode <$> readTVar tbl |
709 | R { rspReflectedIP = Just sockaddr } | 717 | when (nodeIP self /= nodeIP naddr) $ do |
710 | -> do | 718 | case msg of |
711 | -- hPutStrLn stderr $ "External: "++show (nodeId naddr,sockaddr) | 719 | R { rspReflectedIP = Just sockaddr } |
712 | atomically $ addVote committee (nodeId naddr) sockaddr | 720 | -> do |
713 | _ -> return () | 721 | -- hPutStrLn stderr $ "External: "++show (nodeId naddr,sockaddr) |
714 | insertNode (mainlineKademlia client committee tbl sched) naddr | 722 | atomically $ addVote committee (nodeId naddr) sockaddr |
723 | _ -> return () | ||
724 | insertNode (mainlineKademlia client committee tbl sched) naddr | ||
715 | 725 | ||
716 | data Ping = Ping deriving Show | 726 | data Ping = Ping deriving Show |
717 | 727 | ||
@@ -809,11 +819,19 @@ ipFamily ip = case ip of | |||
809 | findNodeH :: Routing -> NodeInfo -> FindNode -> IO NodeFound | 819 | findNodeH :: Routing -> NodeInfo -> FindNode -> IO NodeFound |
810 | findNodeH routing addr (FindNode node iptyp) = do | 820 | findNodeH routing addr (FindNode node iptyp) = do |
811 | let preferred = prefer4or6 addr iptyp | 821 | let preferred = prefer4or6 addr iptyp |
812 | ks <- bool (return []) (go $ routing4 routing) (preferred /= Want_IP6) | 822 | |
813 | ks6 <- bool (return []) (go $ routing6 routing) (preferred /= Want_IP4) | 823 | (append4,append6) <- atomically $ do |
824 | ni4 <- R.thisNode <$> readTVar (routing4 routing) | ||
825 | ni6 <- R.thisNode <$> readTVar (routing6 routing) | ||
826 | return $ case ipFamily (nodeIP addr) of | ||
827 | Want_IP4 -> (id, (++ [ni6])) | ||
828 | Want_IP6 -> ((++ [ni4]), id) | ||
829 | ks <- bool (return []) (go append4 $ routing4 routing) (preferred /= Want_IP6) | ||
830 | ks6 <- bool (return []) (go append6 $ routing6 routing) (preferred /= Want_IP4) | ||
814 | return $ NodeFound ks ks6 | 831 | return $ NodeFound ks ks6 |
815 | where | 832 | where |
816 | go var = R.kclosest mainlineSpace k node <$> atomically (readTVar var) | 833 | go f var = f . R.kclosest mainlineSpace k node <$> atomically (readTVar var) |
834 | |||
817 | k = R.defaultK | 835 | k = R.defaultK |
818 | 836 | ||
819 | 837 | ||
diff --git a/bittorrent.cabal b/bittorrent.cabal index 4af89b97..f985f76b 100644 --- a/bittorrent.cabal +++ b/bittorrent.cabal | |||
@@ -92,6 +92,7 @@ library | |||
92 | Tasks | 92 | Tasks |
93 | Kademlia | 93 | Kademlia |
94 | Mainline | 94 | Mainline |
95 | Global6 | ||
95 | 96 | ||
96 | build-depends: base | 97 | build-depends: base |
97 | , containers | 98 | , containers |
@@ -119,6 +120,7 @@ library | |||
119 | , cereal | 120 | , cereal |
120 | , http-types | 121 | , http-types |
121 | 122 | ||
123 | , process | ||
122 | , split | 124 | , split |
123 | , pretty | 125 | , pretty |
124 | , convertible | 126 | , convertible |