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