summaryrefslogtreecommitdiff
path: root/src/Network/Kademlia/Routing.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/Kademlia/Routing.hs')
-rw-r--r--src/Network/Kademlia/Routing.hs808
1 files changed, 0 insertions, 808 deletions
diff --git a/src/Network/Kademlia/Routing.hs b/src/Network/Kademlia/Routing.hs
deleted file mode 100644
index a52cca73..00000000
--- a/src/Network/Kademlia/Routing.hs
+++ /dev/null
@@ -1,808 +0,0 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- (c) Joe Crayne 2017
4-- License : BSD3
5-- Maintainer : pxqr.sta@gmail.com
6-- Stability : experimental
7-- Portability : portable
8--
9-- Every node maintains a routing table of known good nodes. The
10-- nodes in the routing table are used as starting points for
11-- queries in the DHT. Nodes from the routing table are returned in
12-- response to queries from other nodes.
13--
14-- For more info see:
15-- <http://www.bittorrent.org/beps/bep_0005.html#routing-table>
16--
17{-# LANGUAGE CPP #-}
18{-# LANGUAGE RecordWildCards #-}
19{-# LANGUAGE BangPatterns #-}
20{-# LANGUAGE RankNTypes #-}
21{-# LANGUAGE ViewPatterns #-}
22{-# LANGUAGE TypeOperators #-}
23{-# LANGUAGE DeriveGeneric #-}
24{-# LANGUAGE DeriveFunctor #-}
25{-# LANGUAGE GADTs #-}
26{-# LANGUAGE ScopedTypeVariables #-}
27{-# LANGUAGE TupleSections #-}
28{-# LANGUAGE StandaloneDeriving, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-}
29{-# OPTIONS_GHC -fno-warn-orphans #-}
30module Network.Kademlia.Routing
31 {-
32 ( -- * BucketList
33 BucketList
34 , Info(..)
35
36 -- * Attributes
37 , BucketCount
38 , defaultBucketCount
39 , BucketSize
40 , defaultBucketSize
41 , NodeCount
42
43 -- * Query
44 , Network.Kademlia.Routing.null
45 , Network.Kademlia.Routing.full
46 , thisId
47 , shape
48 , Network.Kademlia.Routing.size
49 , Network.Kademlia.Routing.depth
50 , compatibleNodeId
51
52 -- * Lookup
53 , K
54 , defaultK
55 , TableKey (..)
56 , kclosest
57
58 -- * Construction
59 , Network.Kademlia.Routing.nullTable
60 , Event(..)
61 , CheckPing(..)
62 , Network.Kademlia.Routing.insert
63
64 -- * Conversion
65 , Network.Kademlia.Routing.TableEntry
66 , Network.Kademlia.Routing.toList
67
68 -- * Routing
69 , Timestamp
70 , getTimestamp
71 ) -} where
72
73import Control.Applicative as A
74import Control.Arrow
75import Control.Monad
76import Data.Function
77import Data.Functor.Contravariant
78import Data.Functor.Identity
79import Data.List as L hiding (insert)
80import Data.Maybe
81import Data.Monoid
82import Data.Wrapper.PSQ as PSQ
83import Data.Serialize as S hiding (Result, Done)
84import qualified Data.Sequence as Seq
85import Data.Time
86import Data.Time.Clock.POSIX
87import Data.Word
88import GHC.Generics
89import Text.PrettyPrint as PP hiding ((<>))
90import Text.PrettyPrint.HughesPJClass (pPrint,Pretty)
91import qualified Data.ByteString as BS
92import Data.Bits
93import Data.Ord
94import Data.Reflection
95import Network.Address
96import Data.Typeable
97import Data.Coerce
98import Data.Hashable
99
100
101-- | Last time the node was responding to our queries.
102--
103-- Not all nodes that we learn about are equal. Some are \"good\" and
104-- some are not. Many nodes using the DHT are able to send queries
105-- and receive responses, but are not able to respond to queries
106-- from other nodes. It is important that each node's routing table
107-- must contain only known good nodes. A good node is a node has
108-- responded to one of our queries within the last 15 minutes. A
109-- node is also good if it has ever responded to one of our queries
110-- and has sent us a query within the last 15 minutes. After 15
111-- minutes of inactivity, a node becomes questionable. Nodes become
112-- bad when they fail to respond to multiple queries in a row. Nodes
113-- that we know are good are given priority over nodes with unknown
114-- status.
115--
116type Timestamp = POSIXTime
117
118getTimestamp :: IO Timestamp
119getTimestamp = do
120 utcTime <- getCurrentTime
121 return $ utcTimeToPOSIXSeconds utcTime
122
123
124
125{-----------------------------------------------------------------------
126 Bucket
127-----------------------------------------------------------------------}
128--
129-- When a k-bucket is full and a new node is discovered for that
130-- k-bucket, the least recently seen node in the k-bucket is
131-- PINGed. If the node is found to be still alive, the new node is
132-- place in a secondary list, a replacement cache. The replacement
133-- cache is used only if a node in the k-bucket stops responding. In
134-- other words: new nodes are used only when older nodes disappear.
135
136-- | Timestamp - last time this node is pinged.
137type NodeEntry ni = Binding ni Timestamp
138
139
140-- | Maximum number of 'NodeInfo's stored in a bucket. Most clients
141-- use this value.
142defaultBucketSize :: Int
143defaultBucketSize = 8
144
145data QueueMethods m elem fifo = QueueMethods
146 { pushBack :: elem -> fifo -> m fifo
147 , popFront :: fifo -> m (Maybe elem, fifo)
148 , emptyQueue :: m fifo
149 }
150
151{-
152fromQ :: Functor m =>
153 ( a -> b )
154 -> ( b -> a )
155 -> QueueMethods m elem a
156 -> QueueMethods m elem b
157fromQ embed project QueueMethods{..} =
158 QueueMethods { pushBack = \e -> fmap embed . pushBack e . project
159 , popFront = fmap (second embed) . popFront . project
160 , emptyQueue = fmap embed emptyQueue
161 }
162-}
163
164seqQ :: QueueMethods Identity ni (Seq.Seq ni)
165seqQ = QueueMethods
166 { pushBack = \e fifo -> pure (fifo Seq.|> e)
167 , popFront = \fifo -> case Seq.viewl fifo of
168 e Seq.:< fifo' -> pure (Just e, fifo')
169 Seq.EmptyL -> pure (Nothing, Seq.empty)
170 , emptyQueue = pure Seq.empty
171 }
172
173type BucketQueue ni = Seq.Seq ni
174
175bucketQ :: QueueMethods Identity ni (BucketQueue ni)
176bucketQ = seqQ
177
178
179data Compare a = Compare (a -> a -> Ordering) (Int -> a -> Int)
180
181contramapC :: (b -> a) -> Compare a -> Compare b
182contramapC f (Compare cmp hsh) = Compare (\a b -> cmp (f a) (f b))
183 (\s x -> hsh s (f x))
184
185newtype Ordered' s a = Ordered a
186 deriving (Show)
187
188-- | Hack to avoid UndecidableInstances
189newtype Shrink a = Shrink a
190 deriving (Show)
191
192type Ordered s a = Ordered' s (Shrink a)
193
194instance Reifies s (Compare a) => Eq (Ordered' s (Shrink a)) where
195 a == b = (compare a b == EQ)
196
197instance Reifies s (Compare a) => Ord (Ordered' s (Shrink a)) where
198 compare a b = cmp (coerce a) (coerce b)
199 where Compare cmp _ = reflect (Proxy :: Proxy s)
200
201instance Reifies s (Compare a) => Hashable (Ordered' s (Shrink a)) where
202 hashWithSalt salt x = hash salt (coerce x)
203 where Compare _ hash = reflect (Proxy :: Proxy s)
204
205-- | Bucket is also limited in its length — thus it's called k-bucket.
206-- When bucket becomes full, we should split it in two lists by
207-- current span bit. Span bit is defined by depth in the routing
208-- table tree. Size of the bucket should be choosen such that it's
209-- very unlikely that all nodes in bucket fail within an hour of
210-- each other.
211data Bucket s ni = Bucket
212 { bktNodes :: !(PSQ (Ordered s ni) Timestamp) -- current routing nodes
213 , bktQ :: !(BucketQueue (Timestamp,ni)) -- replacements pending time-outs
214 } deriving (Generic)
215
216#define CAN_SHOW_BUCKET 0
217
218#if CAN_SHOW_BUCKET
219deriving instance Show ni => Show (Bucket s ni)
220#endif
221
222bucketCompare :: forall p ni s. Reifies s (Compare ni) => p (Bucket s ni) -> Compare ni
223bucketCompare _ = reflect (Proxy :: Proxy s)
224
225mapBucket :: ( Reifies s (Compare a)
226 , Reifies t (Compare ni)
227 ) => (a -> ni) -> Bucket s a -> Bucket t ni
228mapBucket f (Bucket ns q) = Bucket (PSQ.fromList $ map (\(ni :-> tm) -> (f' ni :-> tm)) $ PSQ.toList ns)
229 (fmap (second f) q)
230 where f' = coerce . f . coerce
231
232
233#if 0
234
235{-
236getGenericNode :: ( Serialize (NodeId)
237 , Serialize ip
238 , Serialize u
239 ) => Get (NodeInfo)
240getGenericNode = do
241 nid <- get
242 naddr <- get
243 u <- get
244 return NodeInfo
245 { nodeId = nid
246 , nodeAddr = naddr
247 , nodeAnnotation = u
248 }
249
250putGenericNode :: ( Serialize (NodeId)
251 , Serialize ip
252 , Serialize u
253 ) => NodeInfo -> Put
254putGenericNode (NodeInfo nid naddr u) = do
255 put nid
256 put naddr
257 put u
258
259instance (Eq ip, Ord (NodeId), Serialize (NodeId), Serialize ip, Serialize u) => Serialize (Bucket) where
260 get = Bucket . psqFromPairList <$> getListOf ( (,) <$> getGenericNode <*> get ) <*> pure (runIdentity $ emptyQueue bucketQ)
261 put = putListOf (\(ni,stamp) -> putGenericNode ni >> put stamp) . psqToPairList . bktNodes
262-}
263
264#endif
265
266psqFromPairList :: (Ord p, PSQKey k) => [(k, p)] -> PSQ k p
267psqFromPairList xs = PSQ.fromList $ map (\(a,b) -> a :-> b) xs
268
269psqToPairList :: ( PSQKey t, Ord t1 ) => PSQ t t1 -> [(t, t1)]
270psqToPairList psq = map (\(a :-> b) -> (a,b)) $ PSQ.toList psq
271
272-- | Update interval, in seconds.
273delta :: NominalDiffTime
274delta = 15 * 60
275
276-- | Should maintain a set of stable long running nodes.
277--
278-- Note: pings are triggerd only when a bucket is full.
279updateBucketForInbound :: ( Coercible t1 t
280 , Alternative f
281 , Reifies s (Compare t1)
282 ) => NominalDiffTime -> t1 -> Bucket s t1 -> f ([t], Bucket s t1)
283updateBucketForInbound curTime info bucket
284 -- Just update timestamp if a node is already in bucket.
285 --
286 -- Note PingResult events should only occur for nodes we requested a ping for,
287 -- and those will always already be in the routing queue and will get their
288 -- timestamp updated here, since 'TryInsert' is called on every inbound packet,
289 -- including ping results.
290 | already_have
291 = pure ( [], map_ns $ PSQ.insertWith max (coerce info) curTime )
292 -- bucket is good, but not full => we can insert a new node
293 | PSQ.size (bktNodes bucket) < defaultBucketSize
294 = pure ( [], map_ns $ PSQ.insert (coerce info) curTime )
295 -- If there are any questionable nodes in the bucket have not been
296 -- seen in the last 15 minutes, the least recently seen node is
297 -- pinged. If any nodes in the bucket are known to have become bad,
298 -- then one is replaced by the new node in the next insertBucket
299 -- iteration.
300 | not (L.null stales)
301 = pure ( stales
302 , bucket { -- Update timestamps so that we don't redundantly ping.
303 bktNodes = updateStamps curTime (coerce stales) $ bktNodes bucket
304 -- Update queue with the pending NodeInfo in case of ping fail.
305 , bktQ = runIdentity $ pushBack bucketQ (curTime,info) $ bktQ bucket } )
306 -- When the bucket is full of good nodes, the new node is simply discarded.
307 -- We must return 'A.empty' here to ensure that bucket splitting happens
308 -- inside 'modifyBucket'.
309 | otherwise = A.empty
310 where
311 -- We (take 1) to keep a 1-to-1 correspondence between pending pings and
312 -- waiting nodes in the bktQ. This way, we don't have to worry about what
313 -- to do with failed pings for which there is no ready replacements.
314 stales = -- One stale:
315 do (n :-> t) <- maybeToList $ PSQ.findMin (bktNodes bucket)
316 guard (t < curTime - delta)
317 return $ coerce n
318 -- All stale:
319 -- map key \$ PSQ.atMost (curTime - delta) $ bktNodes bucket
320
321 already_have = maybe False (const True) $ PSQ.lookup (coerce info) (bktNodes bucket)
322
323 map_ns f = bucket { bktNodes = f (bktNodes bucket) }
324 -- map_q f = bucket { bktQ = runIdentity \$ f (bktQ bucket) }
325
326updateBucketForPingResult :: (Applicative f, Reifies s (Compare a)) =>
327 a -> Bool -> Bucket s a -> f ([(a, Maybe (Timestamp, a))], Bucket s a)
328updateBucketForPingResult bad_node got_response bucket
329 = pure ( map (,Nothing) forgotten
330 ++ map (second Just) replacements
331 , Bucket (foldr replace
332 (bktNodes bucket)
333 replacements)
334 popped
335 )
336 where
337 (top, popped) = runIdentity $ popFront bucketQ (bktQ bucket)
338
339 -- Dropped from accepted, replaced by pending.
340 replacements | got_response = [] -- Timestamp was already updated by TryInsert.
341 | Just info <- top = do
342 -- Insert only if there's a removal.
343 _ <- maybeToList $ PSQ.lookup (coerce bad_node) (bktNodes bucket)
344 return (bad_node, info)
345 | otherwise = []
346
347 -- Dropped from the pending queue without replacing.
348 forgotten | got_response = maybeToList $ fmap snd top
349 | otherwise = []
350
351
352 replace (bad_node, (tm, info)) =
353 PSQ.insert (coerce info) tm
354 . PSQ.delete (coerce bad_node)
355
356
357updateStamps :: PSQKey ni => Timestamp -> [ni] -> PSQ ni Timestamp -> PSQ ni Timestamp
358updateStamps curTime stales nodes = foldl' (\q n -> PSQ.insert n curTime q) nodes stales
359
360type BitIx = Word
361
362partitionQ :: Monad f => QueueMethods f elem b -> (elem -> Bool) -> b -> f (b, b)
363partitionQ imp test q0 = do
364 pass0 <- emptyQueue imp
365 fail0 <- emptyQueue imp
366 let flipfix a b f = fix f a b
367 flipfix q0 (pass0,fail0) $ \rec q qs -> do
368 (mb,q') <- popFront imp q
369 case mb of
370 Nothing -> return qs
371 Just e -> do qs' <- select (pushBack imp e) qs
372 rec q' qs'
373 where
374 select :: Functor f => (b -> f b) -> (b, b) -> f (b, b)
375 select f = if test e then \(a,b) -> flip (,) b <$> f a
376 else \(a,b) -> (,) a <$> f b
377
378
379
380split :: -- ( Eq ip , Ord (NodeId) , FiniteBits (NodeId)) =>
381 forall ni s. ( Reifies s (Compare ni) ) =>
382 (ni -> Word -> Bool)
383 -> BitIx -> Bucket s ni -> (Bucket s ni, Bucket s ni)
384split testNodeIdBit i b = (Bucket ns qs, Bucket ms rs)
385 where
386 (ns,ms) = (PSQ.fromList *** PSQ.fromList) . partition (spanBit . coerce . key) . PSQ.toList $ bktNodes b
387 (qs,rs) = runIdentity $ partitionQ bucketQ (spanBit . snd) $ bktQ b
388
389 spanBit :: ni -> Bool
390 spanBit entry = testNodeIdBit entry i
391
392
393{-----------------------------------------------------------------------
394-- BucketList
395-----------------------------------------------------------------------}
396
397defaultBucketCount :: Int
398defaultBucketCount = 20
399
400defaultMaxBucketCount :: Word
401defaultMaxBucketCount = 24
402
403data Info ni nid = Info
404 { myBuckets :: BucketList ni
405 , myNodeId :: nid
406 , myAddress :: SockAddr
407 }
408 deriving Generic
409
410deriving instance (Eq ni, Eq nid) => Eq (Info ni nid)
411deriving instance (Show ni, Show nid) => Show (Info ni nid)
412
413-- instance (Eq ip, Serialize ip) => Serialize (Info ip)
414
415-- | The routing table covers the entire 'NodeId' space from 0 to 2 ^
416-- 160. The routing table is subdivided into 'Bucket's that each cover
417-- a portion of the space. An empty table has one bucket with an ID
418-- space range of @min = 0, max = 2 ^ 160@. When a node with ID \"N\"
419-- is inserted into the table, it is placed within the bucket that has
420-- @min <= N < max@. An empty table has only one bucket so any node
421-- must fit within it. Each bucket can only hold 'K' nodes, currently
422-- eight, before becoming 'Full'. When a bucket is full of known good
423-- nodes, no more nodes may be added unless our own 'NodeId' falls
424-- within the range of the 'Bucket'. In that case, the bucket is
425-- replaced by two new buckets each with half the range of the old
426-- bucket and the nodes from the old bucket are distributed among the
427-- two new ones. For a new table with only one bucket, the full bucket
428-- is always split into two new buckets covering the ranges @0..2 ^
429-- 159@ and @2 ^ 159..2 ^ 160@.
430--
431data BucketList ni = forall s. Reifies s (Compare ni) =>
432 BucketList { thisNode :: !ni
433 -- | Non-empty list of buckets.
434 , buckets :: [Bucket s ni]
435 }
436
437mapTable :: (b -> t) -> (t -> b) -> BucketList t -> BucketList b
438mapTable g f tbl@(BucketList self bkts) = reify (contramapC g $ bucketCompare bkts)
439 $ \p -> BucketList
440 { thisNode = f self
441 , buckets = map (resolve p . mapBucket f) bkts
442 }
443 where
444 resolve :: Proxy s -> Bucket s ni -> Bucket s ni
445 resolve = const id
446
447instance (Eq ni) => Eq (BucketList ni) where
448 (==) = (==) `on` Network.Kademlia.Routing.toList
449
450#if 0
451
452instance Serialize NominalDiffTime where
453 put = putWord32be . fromIntegral . fromEnum
454 get = (toEnum . fromIntegral) <$> getWord32be
455
456#endif
457
458#if CAN_SHOW_BUCKET
459deriving instance (Show ni) => Show (BucketList ni)
460#else
461instance Show ni => Show (BucketList ni) where
462 showsPrec d (BucketList self bkts) =
463 mappend "BucketList "
464 . showsPrec (d+1) self
465 . mappend " (fromList "
466 . showsPrec (d+1) (L.map (L.map tableEntry . PSQ.toList . bktNodes) $ bkts)
467 . mappend ") "
468#endif
469
470#if 0
471
472-- | Normally, routing table should be saved between invocations of
473-- the client software. Note that you don't need to store /this/
474-- 'NodeId' since it is already included in routing table.
475instance (Eq ip, Serialize ip, Ord (NodeId), Serialize (NodeId), Serialize u) => Serialize (BucketList)
476
477#endif
478
479-- | Shape of the table.
480instance Pretty (BucketList ni) where
481 pPrint t
482 | bucketCount < 6 = hcat $ punctuate ", " $ L.map PP.int ss
483 | otherwise = brackets $
484 PP.int (L.sum ss) <> " nodes, " <>
485 PP.int bucketCount <> " buckets"
486 where
487 bucketCount = L.length ss
488 ss = shape t
489
490-- | Empty table with specified /spine/ node id.
491--
492-- XXX: The comparison function argument is awkward here.
493nullTable :: (ni -> ni -> Ordering) -> (Int -> ni -> Int) -> ni -> Int -> BucketList ni
494nullTable cmp hsh ni n =
495 reify (Compare cmp hsh)
496 $ \p -> BucketList
497 ni
498 [Bucket (empty p) (runIdentity $ emptyQueue bucketQ)]
499 where
500 empty :: Reifies s (Compare ni) => Proxy s -> PSQ (Ordered s ni) Timestamp
501 empty = const $ PSQ.empty
502
503#if 0
504
505-- | Test if table is empty. In this case DHT should start
506-- bootstrapping process until table becomes 'full'.
507null :: BucketList -> Bool
508null (Tip _ _ b) = PSQ.null $ bktNodes b
509null _ = False
510
511-- | Test if table have maximum number of nodes. No more nodes can be
512-- 'insert'ed, except old ones becomes bad.
513full :: BucketList -> Bool
514full (Tip _ n _) = n == 0
515full (Zero t b) = PSQ.size (bktNodes b) == defaultBucketSize && full t
516full (One b t) = PSQ.size (bktNodes b) == defaultBucketSize && full t
517
518-- | Get the /spine/ node id.
519thisId :: BucketList -> NodeId
520thisId (Tip nid _ _) = nid
521thisId (Zero table _) = thisId table
522thisId (One _ table) = thisId table
523
524-- | Number of nodes in a bucket or a table.
525type NodeCount = Int
526
527#endif
528
529-- | Internally, routing table is similar to list of buckets or a
530-- /matrix/ of nodes. This function returns the shape of the matrix.
531shape :: BucketList ni -> [Int]
532shape (BucketList _ tbl) = map (PSQ.size . bktNodes) tbl
533
534#if 0
535
536-- | Get number of nodes in the table.
537size :: BucketList -> NodeCount
538size = L.sum . shape
539
540-- | Get number of buckets in the table.
541depth :: BucketList -> BucketCount
542depth = L.length . shape
543
544#endif
545
546lookupBucket :: forall ni nid x.
547 ( -- FiniteBits nid
548 Ord nid
549 ) => KademliaSpace nid ni -> nid -> (forall s. Reifies s (Compare ni) => [Bucket s ni] -> x) -> BucketList ni -> x
550lookupBucket space nid kont (BucketList self bkts) = kont $ go 0 [] bkts
551 where
552 d = kademliaXor space nid (kademliaLocation space self)
553
554 go :: Word -> [Bucket s ni] -> [Bucket s ni] -> [Bucket s ni]
555 go i bs (bucket : buckets)
556 | kademliaTestBit space d i = bucket : buckets ++ bs
557 | otherwise = go (succ i) (bucket:bs) buckets
558 go _ bs [] = bs
559
560bucketNumber :: forall ni nid.
561 KademliaSpace nid ni -> nid -> BucketList ni -> Int
562bucketNumber space nid (BucketList self bkts) = fromIntegral $ go 0 bkts
563 where
564 d = kademliaXor space nid (kademliaLocation space self)
565
566 go :: Word -> [Bucket s ni] -> Word
567 go i (bucket : buckets)
568 | kademliaTestBit space d i = i
569 | otherwise = go (succ i) buckets
570 go i [] = i
571
572
573compatibleNodeId :: forall ni nid.
574 ( Serialize nid, FiniteBits nid) =>
575 (ni -> nid) -> BucketList ni -> IO nid
576compatibleNodeId nodeId tbl = genBucketSample prefix br
577 where
578 br = bucketRange (L.length (shape tbl) - 1) True
579 nodeIdSize = finiteBitSize (undefined :: nid) `div` 8
580 bs = BS.pack $ take nodeIdSize $ tablePrefix (testIdBit . nodeId) tbl ++ repeat 0
581 prefix = either error id $ S.decode bs
582
583tablePrefix :: (ni -> Word -> Bool) -> BucketList ni -> [Word8]
584tablePrefix testbit = map (packByte . take 8 . (++repeat False))
585 . chunksOf 8
586 . tableBits testbit
587 where
588 packByte = foldl1' (.|.) . zipWith bitmask [7,6 .. 0]
589 bitmask ix True = bit ix
590 bitmask _ _ = 0
591
592tableBits :: (ni -> Word -> Bool) -> BucketList ni -> [Bool]
593tableBits testbit (BucketList self bkts) =
594 zipWith const (map (testbit self) [0..])
595 bkts
596
597selfNode :: BucketList ni -> ni
598selfNode (BucketList self _) = self
599
600chunksOf :: Int -> [e] -> [[e]]
601chunksOf i ls = map (take i) (build (splitter ls)) where
602 splitter :: [e] -> ([e] -> a -> a) -> a -> a
603 splitter [] _ n = n
604 splitter l c n = l `c` splitter (drop i l) c n
605
606build :: ((a -> [a] -> [a]) -> [a] -> [a]) -> [a]
607build g = g (:) []
608
609
610
611-- | Count of closest nodes in find_node reply.
612type K = Int
613
614-- | Default 'K' is equal to 'defaultBucketSize'.
615defaultK :: K
616defaultK = 8
617
618#if 0
619class TableKey dht k where
620 toNodeId :: k -> NodeId
621
622instance TableKey dht (NodeId) where
623 toNodeId = id
624
625#endif
626
627-- | In Kademlia, the distance metric is XOR and the result is
628-- interpreted as an unsigned integer.
629newtype NodeDistance nodeid = NodeDistance nodeid
630 deriving (Eq, Ord)
631
632-- | distance(A,B) = |A xor B| Smaller values are closer.
633distance :: Bits nid => nid -> nid -> NodeDistance nid
634distance a b = NodeDistance $ xor a b
635
636-- | Order by closeness: nearest nodes first.
637rank :: ( Ord nid
638 ) => KademliaSpace nid ni -> nid -> [ni] -> [ni]
639rank space nid = L.sortBy (comparing (kademliaXor space nid . kademliaLocation space))
640
641
642-- | Get a list of /K/ closest nodes using XOR metric. Used in
643-- 'find_node' and 'get_peers' queries.
644kclosest :: ( -- FiniteBits nid
645 Ord nid
646 ) =>
647 KademliaSpace nid ni -> Int -> nid -> BucketList ni -> [ni]
648kclosest space k nid tbl = take k $ rank space nid (L.concat bucket)
649 ++ rank space nid (L.concat everyone)
650 where
651 (bucket,everyone) =
652 L.splitAt 1
653 . lookupBucket space nid (L.map (coerce . L.map PSQ.key . PSQ.toList . bktNodes))
654 $ tbl
655
656
657
658{-----------------------------------------------------------------------
659-- Routing
660-----------------------------------------------------------------------}
661
662splitTip :: -- ( Eq ip , Ord (NodeId) , FiniteBits (NodeId)) =>
663 ( Reifies s (Compare ni) ) =>
664 (ni -> Word -> Bool)
665 -> ni -> BitIx -> Bucket s ni -> [ Bucket s ni ]
666splitTip testNodeBit ni i bucket
667 | testNodeBit ni i = [zeros , ones ]
668 | otherwise = [ones , zeros ]
669 where
670 (ones, zeros) = split testNodeBit i bucket
671
672-- | Used in each query.
673--
674-- TODO: Kademlia non-empty subtrees should should split if they have less than
675-- k nodes in them. Which subtrees I mean is illustrated in Fig 1. of Kademlia
676-- paper. The rule requiring additional splits is in section 2.4.
677modifyBucket
678 :: -- ( Eq ip , Ord (NodeId) , FiniteBits (NodeId)) =>
679 forall ni nid xs.
680 KademliaSpace nid ni
681 -> nid -> (forall s. Reifies s (Compare ni) => Bucket s ni -> Maybe (xs, Bucket s ni)) -> BucketList ni -> Maybe (xs,BucketList ni)
682modifyBucket space nid f (BucketList self bkts)
683 = second (BucketList self) <$> go (0 :: BitIx) bkts
684 where
685 d = kademliaXor space nid (kademliaLocation space self)
686
687 -- go :: BitIx -> [Bucket s ni] -> Maybe (xs, [Bucket s ni])
688
689 go !i (bucket : buckets@(_:_))
690 | kademliaTestBit space d i = second (: buckets) <$> f bucket
691 | otherwise = second (bucket :) <$> go (succ i) buckets
692
693 go !i [bucket] = second (: []) <$> f bucket <|> gosplit
694 where
695 gosplit | i < defaultMaxBucketCount = go i (splitTip ( kademliaTestBit space
696 . kademliaLocation space )
697 self
698 i
699 bucket)
700 | otherwise = Nothing -- Limit the number of buckets.
701
702
703bktCount :: BucketList ni -> Int
704bktCount (BucketList _ bkts) = L.length bkts
705
706-- | Triggering event for atomic table update
707data Event ni = TryInsert { foreignNode :: ni }
708 | PingResult { foreignNode :: ni , ponged :: Bool }
709
710#if 0
711deriving instance Eq (NodeId) => Eq (Event)
712deriving instance ( Show ip
713 , Show (NodeId)
714 , Show u
715 ) => Show (Event)
716
717#endif
718
719eventId :: (ni -> nid) -> Event ni -> nid
720eventId nodeId (TryInsert ni) = nodeId ni
721eventId nodeId (PingResult ni _) = nodeId ni
722
723
724-- | Actions requested by atomic table update
725data CheckPing ni = CheckPing [ni]
726
727#if 0
728
729deriving instance Eq (NodeId) => Eq (CheckPing)
730deriving instance ( Show ip
731 , Show (NodeId)
732 , Show u
733 ) => Show (CheckPing)
734
735#endif
736
737
738-- | Call on every inbound packet (including requested ping results).
739-- Returns a triple (was_inserted, to_ping, tbl') where
740--
741-- [ /was_inserted/ ] True if the node was added to the routing table.
742--
743-- [ /to_ping/ ] A list of nodes to ping and then run 'updateForPingResult'.
744-- This will be empty if /was_inserted/, but a non-inserted node
745-- may be added to a replacement queue and will be inserted if
746-- one of the items in this list time out.
747--
748-- [ /tbl'/ ] The updated routing 'BucketList'.
749--
750updateForInbound ::
751 KademliaSpace nid ni
752 -> Timestamp -> ni -> BucketList ni -> (Bool, [ni], BucketList ni)
753updateForInbound space tm ni tbl@(BucketList _ bkts) =
754 maybe (False, [],tbl) (\(ps,tbl') -> (True, ps, tbl'))
755 $ modifyBucket space
756 (kademliaLocation space ni)
757 (updateBucketForInbound tm ni)
758 tbl
759
760-- | Update the routing table with the results of a ping.
761--
762-- Each (a,(tm,b)) in the returned list indicates that the node /a/ was deleted from the
763-- routing table and the node /b/, with timestamp /tm/, has taken its place.
764updateForPingResult ::
765 KademliaSpace nid ni
766 -> ni -- ^ The pinged node.
767 -> Bool -- ^ True if we got a reply, False if it timed out.
768 -> BucketList ni -- ^ The routing table.
769 -> ( [(ni,Maybe (Timestamp, ni))], BucketList ni )
770updateForPingResult space ni got_reply tbl =
771 fromMaybe ([],tbl)
772 $ modifyBucket space
773 (kademliaLocation space ni)
774 (updateBucketForPingResult ni got_reply)
775 tbl
776
777
778{-----------------------------------------------------------------------
779-- Conversion
780-----------------------------------------------------------------------}
781
782type TableEntry ni = (ni, Timestamp)
783
784tableEntry :: NodeEntry ni -> TableEntry ni
785tableEntry (a :-> b) = (a, b)
786
787toList :: BucketList ni -> [[TableEntry ni]]
788toList (BucketList _ bkts) = coerce $ L.map (L.map tableEntry . PSQ.toList . bktNodes) bkts
789
790data KademliaSpace nid ni = KademliaSpace
791 { -- | Given a node record (probably including IP address), yields a
792 -- kademlia xor-metric location.
793 kademliaLocation :: ni -> nid
794 -- | Used when comparing locations. This is similar to
795 -- 'Data.Bits.testBit' except that the ordering of bits is reversed, so
796 -- that 0 is the most significant bit.
797 , kademliaTestBit :: nid -> Word -> Bool
798 -- | The Kademlia xor-metric.
799 , kademliaXor :: nid -> nid -> nid
800
801 , kademliaSample :: forall m. Applicative m => (Int -> m BS.ByteString) -> nid -> (Int,Word8,Word8) -> m nid
802 }
803
804instance Contravariant (KademliaSpace nid) where
805 contramap f ks = ks
806 { kademliaLocation = kademliaLocation ks . f
807 }
808