diff options
author | joe <joe@jerkface.net> | 2017-07-25 06:17:46 -0400 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-07-25 06:17:46 -0400 |
commit | 4060c2c717eeac95dd16f9222184d6b4e998cb7f (patch) | |
tree | e38b3b366fc7b3121800fc4390264d4d02a0e368 /Kademlia.hs | |
parent | 895f5da85bc18640db7194df7553db84abb7f29a (diff) |
Fixes to IPv4 bootstrap.
Diffstat (limited to 'Kademlia.hs')
-rw-r--r-- | Kademlia.hs | 45 |
1 files changed, 33 insertions, 12 deletions
diff --git a/Kademlia.hs b/Kademlia.hs index 2c2ff2b9..fdc1fdd2 100644 --- a/Kademlia.hs +++ b/Kademlia.hs | |||
@@ -8,6 +8,7 @@ module Kademlia where | |||
8 | 8 | ||
9 | import Data.Function | 9 | import Data.Function |
10 | import Data.Maybe | 10 | import Data.Maybe |
11 | import qualified Data.Set as Set | ||
11 | import Data.Time.Clock (getCurrentTime) | 12 | import Data.Time.Clock (getCurrentTime) |
12 | import Data.Time.Clock.POSIX (getPOSIXTime, utcTimeToPOSIXSeconds) | 13 | import Data.Time.Clock.POSIX (getPOSIXTime, utcTimeToPOSIXSeconds) |
13 | import Network.DHT.Routing as R | 14 | import Network.DHT.Routing as R |
@@ -17,6 +18,7 @@ import Control.Concurrent.Lifted.Instrument | |||
17 | import Control.Concurrent.Lifted | 18 | import Control.Concurrent.Lifted |
18 | import GHC.Conc (labelThread) | 19 | import GHC.Conc (labelThread) |
19 | #endif | 20 | #endif |
21 | import Control.Concurrent.Async.Pool | ||
20 | import Control.Concurrent.STM | 22 | import Control.Concurrent.STM |
21 | import Control.Monad | 23 | import Control.Monad |
22 | import Data.Bits | 24 | import Data.Bits |
@@ -33,7 +35,7 @@ import Network.DatagramServer.Types (genBucketSample) | |||
33 | import System.Timeout | 35 | import System.Timeout |
34 | import Text.PrettyPrint as PP hiding (($$), (<>)) | 36 | import Text.PrettyPrint as PP hiding (($$), (<>)) |
35 | import Text.PrettyPrint.HughesPJClass hiding (($$), (<>)) | 37 | import Text.PrettyPrint.HughesPJClass hiding (($$), (<>)) |
36 | import Control.Concurrent.Async.Pool | 38 | import System.IO |
37 | 39 | ||
38 | -- | The status of a given node with respect to a given routint table. | 40 | -- | The status of a given node with respect to a given routint table. |
39 | data RoutingStatus | 41 | data RoutingStatus |
@@ -264,7 +266,7 @@ forkPollForRefresh interval psq refresh = do | |||
264 | again | 266 | again |
265 | 267 | ||
266 | refreshBucket :: forall nid ni addr. | 268 | refreshBucket :: forall nid ni addr. |
267 | ( 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 ) => |
268 | Search nid addr ni ni -> TVar (BucketList ni) -> nid -> Int -> IO () | 270 | Search nid addr ni ni -> TVar (BucketList ni) -> nid -> Int -> IO () |
269 | refreshBucket sch var nid n = do | 271 | refreshBucket sch var nid n = do |
270 | tbl <- atomically (readTVar var) | 272 | tbl <- atomically (readTVar var) |
@@ -272,25 +274,35 @@ refreshBucket sch var nid n = do | |||
272 | then return nid -- Yes? Search our own id. | 274 | then return nid -- Yes? Search our own id. |
273 | else genBucketSample nid -- No? Generate a random id. | 275 | else genBucketSample nid -- No? Generate a random id. |
274 | (bucketRange n (n + 1 < bktCount tbl)) | 276 | (bucketRange n (n + 1 < bktCount tbl)) |
275 | resultCounter <- atomically $ newTVar 0 | 277 | resultCounter <- atomically $ newTVar Set.empty |
276 | let fullcount = R.defaultBucketSize | 278 | let fullcount = R.defaultBucketSize |
277 | let checkBucketFull :: ni -> STM Bool | 279 | let checkBucketFull :: ni -> STM Bool |
278 | checkBucketFull found_node = do | 280 | checkBucketFull found_node = do |
279 | tbl <- readTVar var | 281 | tbl <- readTVar var |
280 | let counts = R.shape tbl | 282 | let counts = R.shape tbl |
281 | when (n == R.bucketNumber (searchSpace sch) (kademliaLocation (searchSpace sch) found_node) tbl) | 283 | when (n == R.bucketNumber (searchSpace sch) (kademliaLocation (searchSpace sch) found_node) tbl) |
282 | $ modifyTVar resultCounter (+ 1) | 284 | $ modifyTVar resultCounter (Set.insert found_node) |
283 | resultCount <- readTVar resultCounter | 285 | resultCount <- readTVar resultCounter |
284 | case drop (n - 1) counts of | 286 | case drop (n - 1) counts of |
285 | (cnt:_) | cnt < fullcount -> return True | 287 | (cnt:_) | cnt < fullcount -> return True |
286 | _ | resultCount + 3 < fullcount -> return True -- +3 because maybe duplicates. | 288 | _ | Set.size resultCount < fullcount -> return True |
287 | _ -> return False | 289 | _ -> return False |
290 | |||
291 | hPutStrLn stderr $ "Start refresh " ++ show (n,sample) | ||
292 | |||
288 | -- Set 15 minute timeout in order to avoid overlapping refreshes. | 293 | -- Set 15 minute timeout in order to avoid overlapping refreshes. |
289 | _ <- timeout (15*60*1000000) $ search sch tbl sample checkBucketFull | 294 | s <- search sch tbl sample $ if n+1 == R.defaultBucketCount |
295 | then const $ return True -- Never short-circuit the last bucket. | ||
296 | else checkBucketFull | ||
297 | _ <- timeout (15*60*1000000) $ do | ||
298 | atomically $ searchIsFinished s >>= check | ||
299 | atomically $ searchCancel s | ||
300 | hPutStrLn stderr $ "Finish refresh " ++ show (n,sample) | ||
290 | return () | 301 | return () |
291 | 302 | ||
292 | bootstrap :: | 303 | bootstrap :: |
293 | ( Serialize nid | 304 | ( Show nid |
305 | , Serialize nid | ||
294 | , FiniteBits nid | 306 | , FiniteBits nid |
295 | , Hashable ni | 307 | , Hashable ni |
296 | , Hashable nid | 308 | , Hashable nid |
@@ -319,13 +331,22 @@ bootstrap sch var ping ns ns0 = do | |||
319 | fix $ \again -> do | 331 | fix $ \again -> do |
320 | tbl <- atomically $ readTVar var | 332 | tbl <- atomically $ readTVar var |
321 | let shp = reverse $ zip (R.shape tbl) [0 .. ] | 333 | let shp = reverse $ zip (R.shape tbl) [0 .. ] |
322 | unfull = dropWhile ( (< R.defaultBucketSize) . fst ) shp | 334 | unfull = filter ( (< R.defaultBucketSize) . fst ) shp |
323 | case take 1 unfull of | 335 | case dropWhile ((> R.defaultBucketCount - 1) . snd) unfull of |
324 | [] -> return () -- Bootstrap complete! | 336 | [] -> do |
337 | when (length shp < R.defaultBucketCount) $ do | ||
338 | -- Not enough buckets, keep trying. | ||
339 | hPutStrLn stderr | ||
340 | $ "Not enough buckets, refresh " ++ show (R.defaultBucketCount - 1) | ||
341 | refreshBucket sch var | ||
342 | (kademliaLocation (searchSpace sch) (thisNode tbl)) | ||
343 | (R.defaultBucketCount - 1) | ||
344 | again | ||
325 | (size,num):_ -> do | 345 | (size,num):_ -> do |
326 | -- If we don't yet have enough buckets, we need to search our own id. | 346 | -- If we don't yet have enough buckets, we need to search our own id. |
327 | -- We indicate that by setting the bucket number to the target. | 347 | -- We indicate that by setting the bucket number to the target. |
328 | let num' | bktCount tbl < R.defaultBucketCount = R.defaultBucketCount - 1 | 348 | let num' | bktCount tbl < R.defaultBucketCount = R.defaultBucketCount - 1 |
329 | | otherwise = num | 349 | | otherwise = num |
350 | hPutStrLn stderr $ "Bucket too small, refresh "++ show (num',(size,num),shp) | ||
330 | refreshBucket sch var (kademliaLocation (searchSpace sch) (thisNode tbl)) num' | 351 | refreshBucket sch var (kademliaLocation (searchSpace sch) (thisNode tbl)) num' |
331 | again | 352 | again |