summaryrefslogtreecommitdiff
path: root/src/Network
diff options
context:
space:
mode:
authorjoe <joe@jerkface.net>2017-07-16 19:28:31 -0400
committerjoe <joe@jerkface.net>2017-07-16 19:28:31 -0400
commit74e89f729750b96b5227e4678f0922b630d71c99 (patch)
tree217faa599daa0ccd745d2d37c825e27dae328b5a /src/Network
parent30b27a0216bd85d4480463450e6f7fa60ed1ed60 (diff)
Removed /nid/ type variable from routing 'Table'.
Diffstat (limited to 'src/Network')
-rw-r--r--src/Network/DHT/Routing.hs69
1 files changed, 38 insertions, 31 deletions
diff --git a/src/Network/DHT/Routing.hs b/src/Network/DHT/Routing.hs
index e2bc5aa9..0004ac09 100644
--- a/src/Network/DHT/Routing.hs
+++ b/src/Network/DHT/Routing.hs
@@ -19,6 +19,7 @@
19{-# LANGUAGE ViewPatterns #-} 19{-# LANGUAGE ViewPatterns #-}
20{-# LANGUAGE TypeOperators #-} 20{-# LANGUAGE TypeOperators #-}
21{-# LANGUAGE DeriveGeneric #-} 21{-# LANGUAGE DeriveGeneric #-}
22{-# LANGUAGE DeriveFunctor #-}
22{-# LANGUAGE ScopedTypeVariables #-} 23{-# LANGUAGE ScopedTypeVariables #-}
23{-# LANGUAGE StandaloneDeriving, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-} 24{-# LANGUAGE StandaloneDeriving, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-}
24{-# OPTIONS_GHC -fno-warn-orphans #-} 25{-# OPTIONS_GHC -fno-warn-orphans #-}
@@ -175,10 +176,13 @@ bucketQ = seqQ
175data Bucket ni = Bucket 176data Bucket ni = Bucket
176 { bktNodes :: !(PSQ ni Timestamp) -- current routing nodes 177 { bktNodes :: !(PSQ ni Timestamp) -- current routing nodes
177 , bktQ :: !(BucketQueue (Timestamp,ni)) -- replacements pending time-outs 178 , bktQ :: !(BucketQueue (Timestamp,ni)) -- replacements pending time-outs
178 } deriving Generic 179 } deriving (Generic)
179 180
180deriving instance Show ni => Show (Bucket ni) 181deriving instance Show ni => Show (Bucket ni)
181 182
183mapBucket :: Ord ni => (a -> ni) -> Bucket a -> Bucket ni
184mapBucket f (Bucket ns q) = Bucket (PSQ.fromList $ map (\(ni :-> tm) -> (f ni :-> tm)) $ PSQ.toList ns)
185 (fmap (second f) q)
182 186
183 187
184#if 0 188#if 0
@@ -335,7 +339,7 @@ defaultBucketCount :: Int
335defaultBucketCount = 20 339defaultBucketCount = 20
336 340
337data Info ni nid = Info 341data Info ni nid = Info
338 { myBuckets :: Table ni nid 342 { myBuckets :: Table ni
339 , myNodeId :: nid 343 , myNodeId :: nid
340 , myAddress :: SockAddr 344 , myAddress :: SockAddr
341 } 345 }
@@ -362,18 +366,22 @@ deriving instance (Show ni, Show nid) => Show (Info ni nid)
362-- is always split into two new buckets covering the ranges @0..2 ^ 366-- is always split into two new buckets covering the ranges @0..2 ^
363-- 159@ and @2 ^ 159..2 ^ 160@. 367-- 159@ and @2 ^ 159..2 ^ 160@.
364-- 368--
365data Table ni nid 369data Table ni
366 -- most nearest bucket 370 -- most nearest bucket
367 = Tip nid Int (Bucket ni) 371 = Tip ni Int (Bucket ni)
368 372
369 -- left biased tree branch 373 -- left biased tree branch
370 | Zero (Table ni nid) (Bucket ni) 374 | Zero (Table ni) (Bucket ni)
371 375
372 -- right biased tree branch 376 -- right biased tree branch
373 | One (Bucket ni) (Table ni nid) 377 | One (Bucket ni) (Table ni)
374 deriving Generic 378 deriving Generic
375 379
376instance (Eq ni, Eq nid) => Eq (Table ni nid) where 380mapTable f (One b t) = One (mapBucket f b) (mapTable f t)
381mapTable f (Zero t b) = Zero (mapTable f t) (mapBucket f b)
382mapTable f (Tip ni n b) = Tip (f ni) n (mapBucket f b)
383
384instance (Eq ni) => Eq (Table ni) where
377 (==) = (==) `on` Network.DHT.Routing.toList 385 (==) = (==) `on` Network.DHT.Routing.toList
378 386
379#if 0 387#if 0
@@ -384,7 +392,7 @@ instance Serialize NominalDiffTime where
384 392
385#endif 393#endif
386 394
387deriving instance (Show ni, Show nid) => Show (Table ni nid) 395deriving instance (Show ni) => Show (Table ni)
388 396
389#if 0 397#if 0
390 398
@@ -396,7 +404,7 @@ instance (Eq ip, Serialize ip, Ord (NodeId), Serialize (NodeId), Serialize u) =>
396#endif 404#endif
397 405
398-- | Shape of the table. 406-- | Shape of the table.
399instance Pretty (Table ni nid) where 407instance Pretty (Table ni) where
400 pPrint t 408 pPrint t
401 | bucketCount < 6 = hcat $ punctuate ", " $ L.map PP.int ss 409 | bucketCount < 6 = hcat $ punctuate ", " $ L.map PP.int ss
402 | otherwise = brackets $ 410 | otherwise = brackets $
@@ -407,8 +415,8 @@ instance Pretty (Table ni nid) where
407 ss = shape t 415 ss = shape t
408 416
409-- | Empty table with specified /spine/ node id. 417-- | Empty table with specified /spine/ node id.
410nullTable :: nid -> Int -> Table ni nid 418nullTable :: ni -> Int -> Table ni
411nullTable nid n = Tip nid (bucketCount (pred n)) (Bucket PSQ.empty (runIdentity $ emptyQueue bucketQ)) 419nullTable ni n = Tip ni (bucketCount (pred n)) (Bucket PSQ.empty (runIdentity $ emptyQueue bucketQ))
412 where 420 where
413 bucketCount x = max 0 (min 159 x) 421 bucketCount x = max 0 (min 159 x)
414 422
@@ -440,7 +448,7 @@ type NodeCount = Int
440 448
441-- | Internally, routing table is similar to list of buckets or a 449-- | Internally, routing table is similar to list of buckets or a
442-- /matrix/ of nodes. This function returns the shape of the matrix. 450-- /matrix/ of nodes. This function returns the shape of the matrix.
443shape :: Table ni nid -> [Int] 451shape :: Table ni -> [Int]
444shape = map (PSQ.size . bktNodes) . toBucketList 452shape = map (PSQ.size . bktNodes) . toBucketList
445 453
446#if 0 454#if 0
@@ -457,7 +465,7 @@ depth = L.length . shape
457 465
458lookupBucket :: ( FiniteBits nid 466lookupBucket :: ( FiniteBits nid
459 , Ord nid 467 , Ord nid
460 ) => nid -> Table ni nid -> [Bucket ni] 468 ) => nid -> Table ni -> [Bucket ni]
461lookupBucket nid = go 0 [] 469lookupBucket nid = go 0 []
462 where 470 where
463 go i bs (Zero table bucket) 471 go i bs (Zero table bucket)
@@ -471,7 +479,7 @@ lookupBucket nid = go 0 []
471 479
472compatibleNodeId :: forall ni nid. 480compatibleNodeId :: forall ni nid.
473 ( Serialize nid, FiniteBits nid) => 481 ( Serialize nid, FiniteBits nid) =>
474 Table ni nid -> IO nid 482 Table ni -> IO nid
475compatibleNodeId tbl = genBucketSample prefix br 483compatibleNodeId tbl = genBucketSample prefix br
476 where 484 where
477 br = bucketRange (L.length (shape tbl) - 1) True 485 br = bucketRange (L.length (shape tbl) - 1) True
@@ -479,7 +487,7 @@ compatibleNodeId tbl = genBucketSample prefix br
479 bs = BS.pack $ take nodeIdSize $ tablePrefix tbl ++ repeat 0 487 bs = BS.pack $ take nodeIdSize $ tablePrefix tbl ++ repeat 0
480 prefix = either error id $ S.decode bs 488 prefix = either error id $ S.decode bs
481 489
482tablePrefix :: Table ni nid -> [Word8] 490tablePrefix :: Table ni -> [Word8]
483tablePrefix = map (packByte . take 8 . (++repeat False)) 491tablePrefix = map (packByte . take 8 . (++repeat False))
484 . chunksOf 8 492 . chunksOf 8
485 . tableBits 493 . tableBits
@@ -488,7 +496,7 @@ tablePrefix = map (packByte . take 8 . (++repeat False))
488 bitmask ix True = bit ix 496 bitmask ix True = bit ix
489 bitmask _ _ = 0 497 bitmask _ _ = 0
490 498
491tableBits :: Table ni nid -> [Bool] 499tableBits :: Table ni -> [Bool]
492tableBits (One _ tbl) = True : tableBits tbl 500tableBits (One _ tbl) = True : tableBits tbl
493tableBits (Zero tbl _) = False : tableBits tbl 501tableBits (Zero tbl _) = False : tableBits tbl
494tableBits (Tip _ _ _) = [] 502tableBits (Tip _ _ _) = []
@@ -540,7 +548,7 @@ rank f nid = L.sortBy (comparing (distance nid . f))
540-- 'find_node' and 'get_peers' queries. 548-- 'find_node' and 'get_peers' queries.
541kclosest :: ( FiniteBits nid 549kclosest :: ( FiniteBits nid
542 , Ord nid 550 , Ord nid
543 ) => (ni -> nid) -> Int -> nid -> Table ni nid -> [ni] 551 ) => (ni -> nid) -> Int -> nid -> Table ni -> [ni]
544kclosest nodeId k nid tbl = take k $ rank nodeId nid (L.concat bucket) 552kclosest nodeId k nid tbl = take k $ rank nodeId nid (L.concat bucket)
545 ++ rank nodeId nid (L.concat everyone) 553 ++ rank nodeId nid (L.concat everyone)
546 where 554 where
@@ -558,12 +566,11 @@ kclosest nodeId k nid tbl = take k $ rank nodeId nid (L.concat bucket)
558 566
559splitTip :: -- ( Eq ip , Ord (NodeId) , FiniteBits (NodeId)) => 567splitTip :: -- ( Eq ip , Ord (NodeId) , FiniteBits (NodeId)) =>
560 Ord ni => 568 Ord ni =>
561 (nid -> Word -> Bool) 569 (ni -> Word -> Bool)
562 -> (ni -> Word -> Bool) 570 -> ni -> Int -> BitIx -> Bucket ni -> Table ni
563 -> nid -> Int -> BitIx -> Bucket ni -> Table ni nid 571splitTip testNodeBit ni n i bucket
564splitTip testIdBit testNodeBit nid n i bucket 572 | testNodeBit ni i = (One zeros (Tip ni (pred n) ones))
565 | testIdBit nid i = (One zeros (Tip nid (pred n) ones)) 573 | otherwise = (Zero (Tip ni (pred n) zeros) ones)
566 | otherwise = (Zero (Tip nid (pred n) zeros) ones)
567 where 574 where
568 (ones, zeros) = split testNodeBit i bucket 575 (ones, zeros) = split testNodeBit i bucket
569 576
@@ -577,10 +584,10 @@ modifyBucket
577 forall ni nid xs. Ord ni => 584 forall ni nid xs. Ord ni =>
578 (nid -> Word -> Bool) 585 (nid -> Word -> Bool)
579 -> (ni -> Word -> Bool) 586 -> (ni -> Word -> Bool)
580 -> nid -> (Bucket ni -> Maybe (xs, Bucket ni)) -> Table ni nid -> Maybe (xs,Table ni nid) 587 -> nid -> (Bucket ni -> Maybe (xs, Bucket ni)) -> Table ni -> Maybe (xs,Table ni)
581modifyBucket testIdBit testNodeBit nodeId f = go (0 :: BitIx) 588modifyBucket testIdBit testNodeBit nodeId f = go (0 :: BitIx)
582 where 589 where
583 go :: BitIx -> Table ni nid -> Maybe (xs, Table ni nid) 590 go :: BitIx -> Table ni -> Maybe (xs, Table ni)
584 go !i (Zero table bucket) 591 go !i (Zero table bucket)
585 | testIdBit nodeId i = second (Zero table) <$> f bucket 592 | testIdBit nodeId i = second (Zero table) <$> f bucket
586 | otherwise = second (`Zero` bucket) <$> go (succ i) table 593 | otherwise = second (`Zero` bucket) <$> go (succ i) table
@@ -590,7 +597,7 @@ modifyBucket testIdBit testNodeBit nodeId f = go (0 :: BitIx)
590 go !i (Tip nid n bucket) 597 go !i (Tip nid n bucket)
591 | n == 0 = second (Tip nid n) <$> f bucket 598 | n == 0 = second (Tip nid n) <$> f bucket
592 | otherwise = second (Tip nid n) <$> f bucket 599 | otherwise = second (Tip nid n) <$> f bucket
593 <|> go i (splitTip testIdBit testNodeBit nid n i bucket) 600 <|> go i (splitTip testNodeBit nid n i bucket)
594 601
595 602
596-- | Triggering event for atomic table update 603-- | Triggering event for atomic table update
@@ -639,7 +646,7 @@ deriving instance ( Show ip
639-- 646--
640updateForInbound :: Ord ni => 647updateForInbound :: Ord ni =>
641 KademliaSpace nid ni 648 KademliaSpace nid ni
642 -> Timestamp -> ni -> Table ni nid -> (Bool, [ni], Table ni nid) 649 -> Timestamp -> ni -> Table ni -> (Bool, [ni], Table ni)
643updateForInbound space tm ni tbl = 650updateForInbound space tm ni tbl =
644 maybe (False, [],tbl) (\(ps,tbl') -> (True, ps, tbl')) 651 maybe (False, [],tbl) (\(ps,tbl') -> (True, ps, tbl'))
645 $ modifyBucket (kademliaTestBit space) 652 $ modifyBucket (kademliaTestBit space)
@@ -656,8 +663,8 @@ updateForPingResult :: Ord ni =>
656 KademliaSpace nid ni 663 KademliaSpace nid ni
657 -> ni -- ^ The pinged node. 664 -> ni -- ^ The pinged node.
658 -> Bool -- ^ True if we got a reply, False if it timed out. 665 -> Bool -- ^ True if we got a reply, False if it timed out.
659 -> Table ni nid -- ^ The routing table. 666 -> Table ni -- ^ The routing table.
660 -> ( [(ni,(Timestamp, ni))], Table ni nid ) 667 -> ( [(ni,(Timestamp, ni))], Table ni )
661updateForPingResult space ni got_reply tbl = 668updateForPingResult space ni got_reply tbl =
662 fromMaybe ([],tbl) 669 fromMaybe ([],tbl)
663 $ modifyBucket (kademliaTestBit space) 670 $ modifyBucket (kademliaTestBit space)
@@ -677,12 +684,12 @@ tableEntry :: NodeEntry ni -> TableEntry ni
677tableEntry (a :-> b) = (a, b) 684tableEntry (a :-> b) = (a, b)
678 685
679-- | Non-empty list of buckets. 686-- | Non-empty list of buckets.
680toBucketList :: Table ni nid -> [Bucket ni] 687toBucketList :: Table ni -> [Bucket ni]
681toBucketList (Tip _ _ b) = [b] 688toBucketList (Tip _ _ b) = [b]
682toBucketList (Zero t b) = b : toBucketList t 689toBucketList (Zero t b) = b : toBucketList t
683toBucketList (One b t) = b : toBucketList t 690toBucketList (One b t) = b : toBucketList t
684 691
685toList :: Table ni nid -> [[TableEntry ni]] 692toList :: Table ni -> [[TableEntry ni]]
686toList = L.map (L.map tableEntry . PSQ.toList . bktNodes) . toBucketList 693toList = L.map (L.map tableEntry . PSQ.toList . bktNodes) . toBucketList
687 694
688data KademliaSpace nid ni = KademliaSpace 695data KademliaSpace nid ni = KademliaSpace