summaryrefslogtreecommitdiff
path: root/src/Network
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network')
-rw-r--r--src/Network/DHT/Routing.hs48
1 files changed, 36 insertions, 12 deletions
diff --git a/src/Network/DHT/Routing.hs b/src/Network/DHT/Routing.hs
index d380c6f2..396c4b1d 100644
--- a/src/Network/DHT/Routing.hs
+++ b/src/Network/DHT/Routing.hs
@@ -93,6 +93,7 @@ import Data.Reflection
93import Network.Address 93import Network.Address
94import Data.Typeable 94import Data.Typeable
95import Data.Coerce 95import Data.Coerce
96import Data.Hashable
96 97
97-- | Last time the node was responding to our queries. 98-- | Last time the node was responding to our queries.
98-- 99--
@@ -172,10 +173,11 @@ bucketQ :: QueueMethods Identity ni (BucketQueue ni)
172bucketQ = seqQ 173bucketQ = seqQ
173 174
174 175
175newtype Compare a = Compare (a -> a -> Ordering) 176data Compare a = Compare (a -> a -> Ordering) (Int -> a -> Int)
176 177
177contramapC :: (b -> a) -> Compare a -> Compare b 178contramapC :: (b -> a) -> Compare a -> Compare b
178contramapC f (Compare cmp) = Compare $ \a b -> cmp (f a) (f b) 179contramapC f (Compare cmp hsh) = Compare (\a b -> cmp (f a) (f b))
180 (\s x -> hsh s (f x))
179 181
180newtype Ordered' s a = Ordered a 182newtype Ordered' s a = Ordered a
181 deriving (Show) 183 deriving (Show)
@@ -191,7 +193,11 @@ instance Reifies s (Compare a) => Eq (Ordered' s (Shrink a)) where
191 193
192instance Reifies s (Compare a) => Ord (Ordered' s (Shrink a)) where 194instance Reifies s (Compare a) => Ord (Ordered' s (Shrink a)) where
193 compare a b = cmp (coerce a) (coerce b) 195 compare a b = cmp (coerce a) (coerce b)
194 where Compare cmp = reflect (Proxy :: Proxy s) 196 where Compare cmp _ = reflect (Proxy :: Proxy s)
197
198instance Reifies s (Compare a) => Hashable (Ordered' s (Shrink a)) where
199 hashWithSalt salt x = hash salt (coerce x)
200 where Compare _ hash = reflect (Proxy :: Proxy s)
195 201
196-- | Bucket is also limited in its length — thus it's called k-bucket. 202-- | Bucket is also limited in its length — thus it's called k-bucket.
197-- When bucket becomes full, we should split it in two lists by 203-- When bucket becomes full, we should split it in two lists by
@@ -204,12 +210,18 @@ data Bucket s ni = Bucket
204 , bktQ :: !(BucketQueue (Timestamp,ni)) -- replacements pending time-outs 210 , bktQ :: !(BucketQueue (Timestamp,ni)) -- replacements pending time-outs
205 } deriving (Generic) 211 } deriving (Generic)
206 212
213#define CAN_SHOW_BUCKET 0
214
215#if CAN_SHOW_BUCKET
207deriving instance Show ni => Show (Bucket s ni) 216deriving instance Show ni => Show (Bucket s ni)
217#endif
208 218
209bucketCompare :: forall p ni s. Reifies s (Compare ni) => p (Bucket s ni) -> Compare ni 219bucketCompare :: forall p ni s. Reifies s (Compare ni) => p (Bucket s ni) -> Compare ni
210bucketCompare _ = reflect (Proxy :: Proxy s) 220bucketCompare _ = reflect (Proxy :: Proxy s)
211 221
212mapBucket :: Reifies t (Compare ni) => (a -> ni) -> Bucket s a -> Bucket t ni 222mapBucket :: ( Reifies s (Compare a)
223 , Reifies t (Compare ni)
224 ) => (a -> ni) -> Bucket s a -> Bucket t ni
213mapBucket f (Bucket ns q) = Bucket (PSQ.fromList $ map (\(ni :-> tm) -> (f' ni :-> tm)) $ PSQ.toList ns) 225mapBucket f (Bucket ns q) = Bucket (PSQ.fromList $ map (\(ni :-> tm) -> (f' ni :-> tm)) $ PSQ.toList ns)
214 (fmap (second f) q) 226 (fmap (second f) q)
215 where f' = coerce . f . coerce 227 where f' = coerce . f . coerce
@@ -248,10 +260,10 @@ instance (Eq ip, Ord (NodeId), Serialize (NodeId), Serialize ip, Serialize u) =>
248 260
249#endif 261#endif
250 262
251psqFromPairList :: (Ord p, Ord k) => [(k, p)] -> PSQ k p 263psqFromPairList :: (Ord p, PSQKey k) => [(k, p)] -> PSQ k p
252psqFromPairList xs = PSQ.fromList $ map (\(a,b) -> a :-> b) xs 264psqFromPairList xs = PSQ.fromList $ map (\(a,b) -> a :-> b) xs
253 265
254psqToPairList :: PSQ t t1 -> [(t, t1)] 266psqToPairList :: ( PSQKey t, Ord t1 ) => PSQ t t1 -> [(t, t1)]
255psqToPairList psq = map (\(a :-> b) -> (a,b)) $ PSQ.toList psq 267psqToPairList psq = map (\(a :-> b) -> (a,b)) $ PSQ.toList psq
256 268
257-- | Update interval, in seconds. 269-- | Update interval, in seconds.
@@ -330,7 +342,7 @@ updateBucketForPingResult bad_node got_response bucket
330 . PSQ.delete (coerce bad_node) 342 . PSQ.delete (coerce bad_node)
331 343
332 344
333updateStamps :: Ord ni => Timestamp -> [ni] -> PSQ ni Timestamp -> PSQ ni Timestamp 345updateStamps :: PSQKey ni => Timestamp -> [ni] -> PSQ ni Timestamp -> PSQ ni Timestamp
334updateStamps curTime stales nodes = foldl' (\q n -> PSQ.insert n curTime q) nodes stales 346updateStamps curTime stales nodes = foldl' (\q n -> PSQ.insert n curTime q) nodes stales
335 347
336type BitIx = Word 348type BitIx = Word
@@ -430,7 +442,19 @@ instance Serialize NominalDiffTime where
430 442
431#endif 443#endif
432 444
445#if CAN_SHOW_BUCKET
433deriving instance (Show ni) => Show (BucketList ni) 446deriving instance (Show ni) => Show (BucketList ni)
447#else
448instance Show ni => Show (BucketList ni) where
449 showsPrec d (BucketList self cnt bkts) =
450 mappend "BucketList "
451 . showsPrec (d+1) self
452 . mappend " "
453 . showsPrec (d+1) cnt
454 . mappend " (fromList "
455 . showsPrec (d+1) (L.map (L.map tableEntry . PSQ.toList . bktNodes) $ bkts)
456 . mappend ") "
457#endif
434 458
435#if 0 459#if 0
436 460
@@ -455,9 +479,9 @@ instance Pretty (BucketList ni) where
455-- | Empty table with specified /spine/ node id. 479-- | Empty table with specified /spine/ node id.
456-- 480--
457-- XXX: The comparison function argument is awkward here. 481-- XXX: The comparison function argument is awkward here.
458nullTable :: (ni -> ni -> Ordering) -> ni -> Int -> BucketList ni 482nullTable :: (ni -> ni -> Ordering) -> (Int -> ni -> Int) -> ni -> Int -> BucketList ni
459nullTable cmp ni n = 483nullTable cmp hsh ni n =
460 reify (Compare cmp) 484 reify (Compare cmp hsh)
461 $ \p -> BucketList 485 $ \p -> BucketList
462 ni 486 ni
463 (bucketCount (pred n)) 487 (bucketCount (pred n))
@@ -465,7 +489,7 @@ nullTable cmp ni n =
465 where 489 where
466 bucketCount x = max 0 (min 159 x) 490 bucketCount x = max 0 (min 159 x)
467 491
468 empty :: Proxy s -> PSQ (p s ni) t 492 empty :: Reifies s (Compare ni) => Proxy s -> PSQ (Ordered s ni) Timestamp
469 empty = const $ PSQ.empty 493 empty = const $ PSQ.empty
470 494
471#if 0 495#if 0
@@ -514,7 +538,7 @@ depth = L.length . shape
514lookupBucket :: forall ni nid x. 538lookupBucket :: forall ni nid x.
515 ( FiniteBits nid 539 ( FiniteBits nid
516 , Ord nid 540 , Ord nid
517 ) => (ni -> nid) -> nid -> (forall s. [Bucket s ni] -> x) -> BucketList ni -> x 541 ) => (ni -> nid) -> nid -> (forall s. Reifies s (Compare ni) => [Bucket s ni] -> x) -> BucketList ni -> x
518lookupBucket nodeId nid kont (BucketList self _ bkts) = kont $ go 0 [] bkts 542lookupBucket nodeId nid kont (BucketList self _ bkts) = kont $ go 0 [] bkts
519 where 543 where
520 d = nid `xor` nodeId self 544 d = nid `xor` nodeId self