diff options
-rw-r--r-- | Kademlia.hs | 18 | ||||
-rw-r--r-- | Mainline.hs | 68 |
2 files changed, 72 insertions, 14 deletions
diff --git a/Kademlia.hs b/Kademlia.hs index fdc1fdd2..4920467a 100644 --- a/Kademlia.hs +++ b/Kademlia.hs | |||
@@ -270,10 +270,11 @@ refreshBucket :: forall nid ni addr. | |||
270 | Search nid addr ni ni -> TVar (BucketList ni) -> nid -> Int -> IO () | 270 | Search nid addr ni ni -> TVar (BucketList ni) -> nid -> Int -> IO () |
271 | refreshBucket sch var nid n = do | 271 | refreshBucket sch var nid n = do |
272 | tbl <- atomically (readTVar var) | 272 | tbl <- atomically (readTVar var) |
273 | sample <- if n+1 == R.defaultBucketCount -- Is this the last bucket? | 273 | let count = bktCount tbl |
274 | then return nid -- Yes? Search our own id. | 274 | sample <- if n+1 >= count -- Is this the last bucket? |
275 | else genBucketSample nid -- No? Generate a random id. | 275 | then return nid -- Yes? Search our own id. |
276 | (bucketRange n (n + 1 < bktCount tbl)) | 276 | else genBucketSample nid -- No? Generate a random id. |
277 | (bucketRange n (n + 1 < count)) | ||
277 | resultCounter <- atomically $ newTVar Set.empty | 278 | resultCounter <- atomically $ newTVar Set.empty |
278 | let fullcount = R.defaultBucketSize | 279 | let fullcount = R.defaultBucketSize |
279 | let checkBucketFull :: ni -> STM Bool | 280 | let checkBucketFull :: ni -> STM Bool |
@@ -315,7 +316,7 @@ bootstrap :: | |||
315 | bootstrap sch var ping ns ns0 = do | 316 | bootstrap sch var ping ns ns0 = do |
316 | -- First, ping the given nodes so that they are added to | 317 | -- First, ping the given nodes so that they are added to |
317 | -- our routing table. | 318 | -- our routing table. |
318 | withTaskGroup 20 $ \g -> do | 319 | withTaskGroup 50 $ \g -> do |
319 | got_response <- or <$> mapConcurrently g ping ns | 320 | got_response <- or <$> mapConcurrently g ping ns |
320 | -- We resort to the hardcoded fallback nodes only when we got no | 321 | -- We resort to the hardcoded fallback nodes only when we got no |
321 | -- responses. This is to lesson the burden on well-known boostrap | 322 | -- responses. This is to lesson the burden on well-known boostrap |
@@ -323,13 +324,20 @@ bootstrap sch var ping ns ns0 = do | |||
323 | when (not got_response) $ do | 324 | when (not got_response) $ do |
324 | _ <- mapConcurrently g ping ns0 | 325 | _ <- mapConcurrently g ping ns0 |
325 | return () | 326 | return () |
327 | |||
328 | mvar <- newMVar () | ||
326 | -- Now run searches until all the buckets are full. On a small network, | 329 | -- Now run searches until all the buckets are full. On a small network, |
327 | -- this may never quit. | 330 | -- this may never quit. |
328 | -- | 331 | -- |
329 | -- TODO: For small networks, we should give up on filling a nearby bucket | 332 | -- TODO: For small networks, we should give up on filling a nearby bucket |
330 | -- at some point and move on to one farther away. | 333 | -- at some point and move on to one farther away. |
331 | fix $ \again -> do | 334 | fix $ \again -> do |
335 | takeMVar mvar | ||
332 | tbl <- atomically $ readTVar var | 336 | tbl <- atomically $ readTVar var |
337 | fork $ do | ||
338 | -- Force a delay in case the search returns too quickly | ||
339 | threadDelay (60 * 1000000) | ||
340 | putMVar mvar () | ||
333 | let shp = reverse $ zip (R.shape tbl) [0 .. ] | 341 | let shp = reverse $ zip (R.shape tbl) [0 .. ] |
334 | unfull = filter ( (< R.defaultBucketSize) . fst ) shp | 342 | unfull = filter ( (< R.defaultBucketSize) . fst ) shp |
335 | case dropWhile ((> R.defaultBucketCount - 1) . snd) unfull of | 343 | case dropWhile ((> R.defaultBucketCount - 1) . snd) unfull of |
diff --git a/Mainline.hs b/Mainline.hs index 911f0dbc..b24f847d 100644 --- a/Mainline.hs +++ b/Mainline.hs | |||
@@ -73,6 +73,9 @@ import Control.Concurrent.Lifted | |||
73 | import GHC.Conc (labelThread) | 73 | import GHC.Conc (labelThread) |
74 | #endif | 74 | #endif |
75 | import Control.Exception (SomeException(..),handle) | 75 | import Control.Exception (SomeException(..),handle) |
76 | import Data.Aeson (FromJSON,ToJSON,(.=)) | ||
77 | import qualified Data.Aeson as JSON | ||
78 | import Text.Read | ||
76 | 79 | ||
77 | newtype NodeId = NodeId ByteString | 80 | newtype NodeId = NodeId ByteString |
78 | deriving (Eq,Ord,ByteArrayAccess, BEncode, Bits, Hashable) | 81 | deriving (Eq,Ord,ByteArrayAccess, BEncode, Bits, Hashable) |
@@ -97,6 +100,36 @@ data NodeInfo = NodeInfo | |||
97 | } | 100 | } |
98 | deriving (Eq,Ord) | 101 | deriving (Eq,Ord) |
99 | 102 | ||
103 | instance ToJSON NodeInfo where | ||
104 | toJSON (NodeInfo nid (IPv4 ip) port) | ||
105 | = JSON.object [ "node-id" .= show nid | ||
106 | , "ipv4" .= show ip | ||
107 | , "port" .= (fromIntegral port :: Int) | ||
108 | ] | ||
109 | toJSON (NodeInfo nid (IPv6 ip6) port) | ||
110 | | Just ip <- un4map ip6 | ||
111 | = JSON.object [ "node-id" .= show nid | ||
112 | , "ipv4" .= show ip | ||
113 | , "port" .= (fromIntegral port :: Int) | ||
114 | ] | ||
115 | | otherwise | ||
116 | = JSON.object [ "node-id" .= show nid | ||
117 | , "ipv6" .= show ip6 | ||
118 | , "port" .= (fromIntegral port :: Int) | ||
119 | ] | ||
120 | instance FromJSON NodeInfo where | ||
121 | parseJSON (JSON.Object v) = do | ||
122 | nidstr <- v JSON..: "node-id" | ||
123 | ip6str <- v JSON..:? "ipv6" | ||
124 | ip4str <- v JSON..:? "ipv4" | ||
125 | portnum <- v JSON..: "port" | ||
126 | ip <- maybe empty (return . IPv6) (ip6str >>= readMaybe) | ||
127 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) | ||
128 | let (bs,_) = Base16.decode (Char8.pack nidstr) | ||
129 | guard (B.length bs == 20) | ||
130 | return $ NodeInfo (NodeId bs) ip (fromIntegral (portnum :: Word16)) | ||
131 | |||
132 | |||
100 | -- The Hashable instance depends only on the IP address and port number. It is | 133 | -- The Hashable instance depends only on the IP address and port number. It is |
101 | -- used to compute the announce token. | 134 | -- used to compute the announce token. |
102 | instance Hashable NodeInfo where | 135 | instance Hashable NodeInfo where |
@@ -145,11 +178,14 @@ putNodeInfo6 (NodeInfo (NodeId nid) (IPv6 ip) port) | |||
145 | putNodeInfo6 _ = return () | 178 | putNodeInfo6 _ = return () |
146 | 179 | ||
147 | 180 | ||
148 | -- TODO: We should use a SocketAddrInet6 address for a dual-stack listen | 181 | -- | TODO: This should depend on the bind address to support IPv4-only. For |
149 | -- socket. Therefore, the behavior of this method should depend on the bind | 182 | -- now, in order to support dual-stack listen, we're going to assume IPv6 is |
150 | -- address for outbound packets. | 183 | -- wanted and map IPv4 addresses accordingly. |
151 | nodeAddr :: NodeInfo -> SockAddr | 184 | nodeAddr :: NodeInfo -> SockAddr |
152 | nodeAddr (NodeInfo _ ip port) = setPort port $ toSockAddr ip | 185 | nodeAddr (NodeInfo _ ip port) = |
186 | case ip of | ||
187 | IPv4 ip4 -> setPort port $ toSockAddr (ipv4ToIPv6 ip4) | ||
188 | IPv6 ip6 -> setPort port $ toSockAddr ip6 | ||
153 | 189 | ||
154 | nodeInfo :: NodeId -> SockAddr -> Either String NodeInfo | 190 | nodeInfo :: NodeId -> SockAddr -> Either String NodeInfo |
155 | nodeInfo nid saddr | 191 | nodeInfo nid saddr |
@@ -503,6 +539,16 @@ newClient addr = do | |||
503 | 539 | ||
504 | -- | Modifies a purely random 'NodeId' to one that is related to a given | 540 | -- | Modifies a purely random 'NodeId' to one that is related to a given |
505 | -- routable address in accordance with BEP 42. | 541 | -- routable address in accordance with BEP 42. |
542 | -- | ||
543 | -- Test vectors from the spec: | ||
544 | -- | ||
545 | -- IP rand example node ID | ||
546 | -- ============ ===== ========================================== | ||
547 | -- 124.31.75.21 1 5fbfbf f10c5d6a4ec8a88e4c6ab4c28b95eee4 01 | ||
548 | -- 21.75.31.124 86 5a3ce9 c14e7a08645677bbd1cfe7d8f956d532 56 | ||
549 | -- 65.23.51.170 22 a5d432 20bc8f112a3d426c84764f8c2a1150e6 16 | ||
550 | -- 84.124.73.14 65 1b0321 dd1bb1fe518101ceef99462b947a01ff 41 | ||
551 | -- 43.213.53.83 90 e56f6c bf5b7c4be0237986d5243b87aa6d5130 5a | ||
506 | bep42 :: SockAddr -> NodeId -> Maybe NodeId | 552 | bep42 :: SockAddr -> NodeId -> Maybe NodeId |
507 | bep42 addr (NodeId r) | 553 | bep42 addr (NodeId r) |
508 | | Just ip <- fmap S.encode (fromSockAddr addr :: Maybe IPv4) | 554 | | Just ip <- fmap S.encode (fromSockAddr addr :: Maybe IPv4) |
@@ -513,10 +559,9 @@ bep42 addr (NodeId r) | |||
513 | where | 559 | where |
514 | ip4mask = "\x03\x0f\x3f\xff" :: ByteString | 560 | ip4mask = "\x03\x0f\x3f\xff" :: ByteString |
515 | ip6mask = "\x01\x03\x07\x0f\x1f\x3f\x7f\xff" :: ByteString | 561 | ip6mask = "\x01\x03\x07\x0f\x1f\x3f\x7f\xff" :: ByteString |
516 | nbhood_select = (B.last r :: Word8) .&. 7 | 562 | nbhood_select = B.last r .&. 7 |
517 | nodeIdSize = 20 | 563 | retr n = pure $ B.drop (B.length r - n) r |
518 | retr n = pure $ B.drop (nodeIdSize - n) $ S.encode r | 564 | crc = S.encode . crc32c . B.pack |
519 | crc = (`B.append` B.replicate 16 0) . S.encode . crc32c . B.pack | ||
520 | applyMask ip = case B.zipWith (.&.) msk ip of | 565 | applyMask ip = case B.zipWith (.&.) msk ip of |
521 | (b:bs) -> (b .|. shiftL nbhood_select 5) : bs | 566 | (b:bs) -> (b .|. shiftL nbhood_select 5) : bs |
522 | bs -> bs | 567 | bs -> bs |
@@ -524,6 +569,7 @@ bep42 addr (NodeId r) | |||
524 | | otherwise = ip6mask | 569 | | otherwise = ip6mask |
525 | 570 | ||
526 | 571 | ||
572 | |||
527 | defaultHandler :: ByteString -> Handler | 573 | defaultHandler :: ByteString -> Handler |
528 | defaultHandler meth = MethodHandler decodePayload errorPayload returnError | 574 | defaultHandler meth = MethodHandler decodePayload errorPayload returnError |
529 | where | 575 | where |
@@ -540,7 +586,11 @@ mainlineKademlia client committee var sched | |||
540 | io2 <- touchBucket mainlineSpace (15*60) var sched tr | 586 | io2 <- touchBucket mainlineSpace (15*60) var sched tr |
541 | return $ do | 587 | return $ do |
542 | io1 >> io2 | 588 | io1 >> io2 |
543 | hPutStrLn stderr ("Buckets: "++show tr) | 589 | hPutStrLn stderr $ unwords |
590 | [ "Buckets: " | ||
591 | , show (transitionedTo tr) | ||
592 | , show (transitioningNode tr) | ||
593 | ] | ||
544 | } | 594 | } |
545 | 595 | ||
546 | 596 | ||