diff options
Diffstat (limited to 'src/Network/BitTorrent/DHT')
-rw-r--r-- | src/Network/BitTorrent/DHT/Message.hs | 4 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Query.hs | 3 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Routing.hs | 268 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Search.hs | 22 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Session.hs | 42 |
5 files changed, 195 insertions, 144 deletions
diff --git a/src/Network/BitTorrent/DHT/Message.hs b/src/Network/BitTorrent/DHT/Message.hs index c3df683a..c99c72bb 100644 --- a/src/Network/BitTorrent/DHT/Message.hs +++ b/src/Network/BitTorrent/DHT/Message.hs | |||
@@ -113,8 +113,10 @@ import Data.Maybe | |||
113 | 113 | ||
114 | import Data.Torrent (InfoHash) | 114 | import Data.Torrent (InfoHash) |
115 | import Network.BitTorrent.DHT.Token | 115 | import Network.BitTorrent.DHT.Token |
116 | #ifdef VERSION_bencoding | ||
116 | import Network.KRPC () | 117 | import Network.KRPC () |
117 | import Network.DHT.Mainline () | 118 | import Network.DHT.Mainline () |
119 | #endif | ||
118 | import Network.RPC hiding (Query,Response) | 120 | import Network.RPC hiding (Query,Response) |
119 | 121 | ||
120 | {----------------------------------------------------------------------- | 122 | {----------------------------------------------------------------------- |
@@ -237,7 +239,7 @@ instance KRPC (Query Ping) (Response Ping) where | |||
237 | #ifdef VERSION_bencoding | 239 | #ifdef VERSION_bencoding |
238 | newtype FindNode ip = FindNode (NodeId KMessageOf) | 240 | newtype FindNode ip = FindNode (NodeId KMessageOf) |
239 | #else | 241 | #else |
240 | data FindNode ip = FindNode NodeId Tox.Nonce8 -- Tox: Get Nodes | 242 | data FindNode ip = FindNode (NodeId Tox.Message) Tox.Nonce8 -- Tox: Get Nodes |
241 | #endif | 243 | #endif |
242 | deriving (Show, Eq, Typeable) | 244 | deriving (Show, Eq, Typeable) |
243 | 245 | ||
diff --git a/src/Network/BitTorrent/DHT/Query.hs b/src/Network/BitTorrent/DHT/Query.hs index 4b386cdc..56ea262a 100644 --- a/src/Network/BitTorrent/DHT/Query.hs +++ b/src/Network/BitTorrent/DHT/Query.hs | |||
@@ -14,6 +14,7 @@ | |||
14 | {-# LANGUAGE ScopedTypeVariables #-} | 14 | {-# LANGUAGE ScopedTypeVariables #-} |
15 | {-# LANGUAGE TemplateHaskell #-} | 15 | {-# LANGUAGE TemplateHaskell #-} |
16 | {-# LANGUAGE TupleSections #-} | 16 | {-# LANGUAGE TupleSections #-} |
17 | {-# LANGUAGE PartialTypeSignatures #-} | ||
17 | {-# LANGUAGE GADTs #-} | 18 | {-# LANGUAGE GADTs #-} |
18 | module Network.BitTorrent.DHT.Query | 19 | module Network.BitTorrent.DHT.Query |
19 | ( -- * Handler | 20 | ( -- * Handler |
@@ -322,7 +323,7 @@ insertNode info witnessed_ip0 = do | |||
322 | let logMsg = "Routing table: " <> pPrint t | 323 | let logMsg = "Routing table: " <> pPrint t |
323 | $(logDebugS) "insertNode" (T.pack (render logMsg)) | 324 | $(logDebugS) "insertNode" (T.pack (render logMsg)) |
324 | let arrival0 = TryInsert info | 325 | let arrival0 = TryInsert info |
325 | arrival4 = TryInsert (mapAddress fromAddr info) :: Event (Maybe IPv4) | 326 | arrival4 = TryInsert (mapAddress fromAddr info) :: Event _ (Maybe IPv4) _ |
326 | $(logDebugS) "insertNode" $ T.pack (show arrival4) | 327 | $(logDebugS) "insertNode" $ T.pack (show arrival4) |
327 | maxbuckets <- asks (optBucketCount . options) | 328 | maxbuckets <- asks (optBucketCount . options) |
328 | fallbackid <- asks tentativeNodeId | 329 | fallbackid <- asks tentativeNodeId |
diff --git a/src/Network/BitTorrent/DHT/Routing.hs b/src/Network/BitTorrent/DHT/Routing.hs index 6cf7f122..42728a53 100644 --- a/src/Network/BitTorrent/DHT/Routing.hs +++ b/src/Network/BitTorrent/DHT/Routing.hs | |||
@@ -13,12 +13,14 @@ | |||
13 | -- For more info see: | 13 | -- For more info see: |
14 | -- <http://www.bittorrent.org/beps/bep_0005.html#routing-table> | 14 | -- <http://www.bittorrent.org/beps/bep_0005.html#routing-table> |
15 | -- | 15 | -- |
16 | {-# LANGUAGE CPP #-} | ||
16 | {-# LANGUAGE RecordWildCards #-} | 17 | {-# LANGUAGE RecordWildCards #-} |
17 | {-# LANGUAGE BangPatterns #-} | 18 | {-# LANGUAGE BangPatterns #-} |
18 | {-# LANGUAGE ViewPatterns #-} | 19 | {-# LANGUAGE ViewPatterns #-} |
19 | {-# LANGUAGE TypeOperators #-} | 20 | {-# LANGUAGE TypeOperators #-} |
20 | {-# LANGUAGE DeriveGeneric #-} | 21 | {-# LANGUAGE DeriveGeneric #-} |
21 | {-# LANGUAGE ScopedTypeVariables #-} | 22 | {-# LANGUAGE ScopedTypeVariables #-} |
23 | {-# LANGUAGE StandaloneDeriving, FlexibleContexts, MultiParamTypeClasses, FlexibleInstances #-} | ||
22 | {-# OPTIONS_GHC -fno-warn-orphans #-} | 24 | {-# OPTIONS_GHC -fno-warn-orphans #-} |
23 | module Network.BitTorrent.DHT.Routing | 25 | module Network.BitTorrent.DHT.Routing |
24 | ( -- * Table | 26 | ( -- * Table |
@@ -59,8 +61,6 @@ module Network.BitTorrent.DHT.Routing | |||
59 | 61 | ||
60 | -- * Routing | 62 | -- * Routing |
61 | , Timestamp | 63 | , Timestamp |
62 | , Routing | ||
63 | , runRouting | ||
64 | ) where | 64 | ) where |
65 | 65 | ||
66 | import Control.Applicative as A | 66 | import Control.Applicative as A |
@@ -83,10 +83,16 @@ import Text.PrettyPrint.HughesPJClass (pPrint,Pretty) | |||
83 | import qualified Data.ByteString as BS | 83 | import qualified Data.ByteString as BS |
84 | import Data.Bits | 84 | import Data.Bits |
85 | 85 | ||
86 | import Network.KRPC.Message (KMessageOf) | ||
87 | import Data.Torrent | 86 | import Data.Torrent |
88 | import Network.BitTorrent.Address | 87 | import Network.BitTorrent.Address |
89 | import Network.DHT.Mainline | 88 | #ifdef VERSION_bencoding |
89 | import Network.DHT.Mainline () | ||
90 | import Network.KRPC.Message (KMessageOf) | ||
91 | #else | ||
92 | import Data.Tox as Tox | ||
93 | type KMessageOf = Tox.Message | ||
94 | #endif | ||
95 | |||
90 | 96 | ||
91 | {----------------------------------------------------------------------- | 97 | {----------------------------------------------------------------------- |
92 | -- Routing monad | 98 | -- Routing monad |
@@ -109,66 +115,6 @@ import Network.DHT.Mainline | |||
109 | -- | 115 | -- |
110 | type Timestamp = POSIXTime | 116 | type Timestamp = POSIXTime |
111 | 117 | ||
112 | -- | Some routing operations might need to perform additional IO. | ||
113 | data Routing ip result | ||
114 | = Full | ||
115 | | Done result | ||
116 | | GetTime ( Timestamp -> Routing ip result) | ||
117 | | NeedPing (NodeAddr ip) ( Bool -> Routing ip result) | ||
118 | | Refresh NodeId (Routing ip result) | ||
119 | |||
120 | instance Functor (Routing ip) where | ||
121 | fmap _ Full = Full | ||
122 | fmap f (Done r) = Done ( f r) | ||
123 | fmap f (GetTime g) = GetTime (fmap f . g) | ||
124 | fmap f (NeedPing addr g) = NeedPing addr (fmap f . g) | ||
125 | fmap f (Refresh nid g) = Refresh nid (fmap f g) | ||
126 | |||
127 | instance Monad (Routing ip) where | ||
128 | return = Done | ||
129 | |||
130 | Full >>= _ = Full | ||
131 | Done r >>= m = m r | ||
132 | GetTime f >>= m = GetTime $ \ t -> f t >>= m | ||
133 | NeedPing a f >>= m = NeedPing a $ \ p -> f p >>= m | ||
134 | Refresh n f >>= m = Refresh n $ f >>= m | ||
135 | |||
136 | instance Applicative (Routing ip) where | ||
137 | pure = return | ||
138 | (<*>) = ap | ||
139 | |||
140 | instance Alternative (Routing ip) where | ||
141 | empty = Full | ||
142 | |||
143 | Full <|> m = m | ||
144 | Done a <|> _ = Done a | ||
145 | GetTime f <|> m = GetTime $ \ t -> f t <|> m | ||
146 | NeedPing a f <|> m = NeedPing a $ \ p -> f p <|> m | ||
147 | Refresh n f <|> m = Refresh n (f <|> m) | ||
148 | |||
149 | -- | Run routing table operation. | ||
150 | runRouting :: Monad m | ||
151 | => (NodeAddr ip -> m Bool) -- ^ ping the specific node; | ||
152 | -> (NodeId -> m ()) -- ^ refresh nodes; | ||
153 | -> m Timestamp -- ^ get current time; | ||
154 | -> Routing ip f -- ^ operation to run; | ||
155 | -> m (Maybe f) -- ^ operation result; | ||
156 | runRouting ping_node find_nodes timestamper = go | ||
157 | where | ||
158 | go Full = return (Nothing) | ||
159 | go (Done r) = return (Just r) | ||
160 | go (GetTime f) = do | ||
161 | t <- timestamper | ||
162 | go (f t) | ||
163 | |||
164 | go (NeedPing addr f) = do | ||
165 | pong <- ping_node addr | ||
166 | go (f pong) | ||
167 | |||
168 | go (Refresh nid f) = do | ||
169 | find_nodes nid | ||
170 | go f | ||
171 | |||
172 | {----------------------------------------------------------------------- | 118 | {----------------------------------------------------------------------- |
173 | Bucket | 119 | Bucket |
174 | -----------------------------------------------------------------------} | 120 | -----------------------------------------------------------------------} |
@@ -182,7 +128,7 @@ runRouting ping_node find_nodes timestamper = go | |||
182 | -- other words: new nodes are used only when older nodes disappear. | 128 | -- other words: new nodes are used only when older nodes disappear. |
183 | 129 | ||
184 | -- | Timestamp - last time this node is pinged. | 130 | -- | Timestamp - last time this node is pinged. |
185 | type NodeEntry ip = Binding (NodeInfo KMessageOf ip ()) Timestamp | 131 | type NodeEntry dht ip u = Binding (NodeInfo dht ip u) Timestamp |
186 | 132 | ||
187 | -- TODO instance Pretty where | 133 | -- TODO instance Pretty where |
188 | 134 | ||
@@ -213,7 +159,7 @@ fromQ embed project QueueMethods{..} = | |||
213 | } | 159 | } |
214 | -} | 160 | -} |
215 | 161 | ||
216 | seqQ :: QueueMethods Identity (NodeInfo KMessageOf ip ()) (Seq.Seq (NodeInfo KMessageOf ip ())) | 162 | seqQ :: QueueMethods Identity (NodeInfo dht ip u) (Seq.Seq (NodeInfo dht ip u)) |
217 | seqQ = QueueMethods | 163 | seqQ = QueueMethods |
218 | { pushBack = \e fifo -> pure (fifo Seq.|> e) | 164 | { pushBack = \e fifo -> pure (fifo Seq.|> e) |
219 | , popFront = \fifo -> case Seq.viewl fifo of | 165 | , popFront = \fifo -> case Seq.viewl fifo of |
@@ -222,9 +168,9 @@ seqQ = QueueMethods | |||
222 | , emptyQueue = pure Seq.empty | 168 | , emptyQueue = pure Seq.empty |
223 | } | 169 | } |
224 | 170 | ||
225 | type BucketQueue ip = Seq.Seq (NodeInfo KMessageOf ip ()) | 171 | type BucketQueue dht ip u = Seq.Seq (NodeInfo dht ip u) |
226 | 172 | ||
227 | bucketQ :: QueueMethods Identity (NodeInfo KMessageOf ip ()) (BucketQueue ip) | 173 | bucketQ :: QueueMethods Identity (NodeInfo dht ip u) (BucketQueue dht ip u) |
228 | bucketQ = seqQ | 174 | bucketQ = seqQ |
229 | 175 | ||
230 | -- | Bucket is also limited in its length — thus it's called k-bucket. | 176 | -- | Bucket is also limited in its length — thus it's called k-bucket. |
@@ -234,16 +180,45 @@ bucketQ = seqQ | |||
234 | -- very unlikely that all nodes in bucket fail within an hour of | 180 | -- very unlikely that all nodes in bucket fail within an hour of |
235 | -- each other. | 181 | -- each other. |
236 | -- | 182 | -- |
237 | data Bucket ip = Bucket { bktNodes :: !(PSQ (NodeInfo KMessageOf ip ()) Timestamp) | 183 | data Bucket dht ip u = Bucket { bktNodes :: !(PSQ (NodeInfo dht ip u) Timestamp) |
238 | , bktQ :: !(BucketQueue ip) | 184 | , bktQ :: !(BucketQueue dht ip u) |
239 | } deriving (Show,Generic) | 185 | } deriving Generic |
240 | 186 | ||
241 | instance (Eq ip, Serialize ip) => Serialize (Bucket ip) where | 187 | deriving instance (Show ip, Show u, Show (NodeId dht)) => Show (Bucket dht ip u) |
242 | get = Bucket . psqFromPairList <$> get <*> pure (runIdentity $ emptyQueue bucketQ) | 188 | |
243 | put = put . psqToPairList . bktNodes | 189 | |
244 | 190 | getGenericNode :: ( Serialize (NodeId dht) | |
191 | , Serialize ip | ||
192 | , Serialize u | ||
193 | ) => Get (NodeInfo dht ip u) | ||
194 | getGenericNode = do | ||
195 | nid <- get | ||
196 | naddr <- get | ||
197 | u <- get | ||
198 | return NodeInfo | ||
199 | { nodeId = nid | ||
200 | , nodeAddr = naddr | ||
201 | , nodeAnnotation = u | ||
202 | } | ||
203 | |||
204 | putGenericNode :: ( Serialize (NodeId dht) | ||
205 | , Serialize ip | ||
206 | , Serialize u | ||
207 | ) => NodeInfo dht ip u -> Put | ||
208 | putGenericNode (NodeInfo nid naddr u) = do | ||
209 | put nid | ||
210 | put naddr | ||
211 | put u | ||
212 | |||
213 | instance (Eq ip, Ord (NodeId dht), Serialize (NodeId dht), Serialize ip, Serialize u) => Serialize (Bucket dht ip u) where | ||
214 | get = Bucket . psqFromPairList <$> getListOf ( (,) <$> getGenericNode <*> get ) <*> pure (runIdentity $ emptyQueue bucketQ) | ||
215 | put = putListOf (\(ni,stamp) -> putGenericNode ni >> put stamp) . psqToPairList . bktNodes | ||
216 | |||
217 | |||
218 | psqFromPairList :: (Ord p, Ord k) => [(k, p)] -> OrdPSQ k p () | ||
245 | psqFromPairList xs = PSQ.fromList $ map (\(a,b) -> a :-> b) xs | 219 | psqFromPairList xs = PSQ.fromList $ map (\(a,b) -> a :-> b) xs |
246 | 220 | ||
221 | psqToPairList :: OrdPSQ t t1 () -> [(t, t1)] | ||
247 | psqToPairList psq = map (\(a :-> b) -> (a,b)) $ PSQ.toList psq | 222 | psqToPairList psq = map (\(a :-> b) -> (a,b)) $ PSQ.toList psq |
248 | 223 | ||
249 | -- | Update interval, in seconds. | 224 | -- | Update interval, in seconds. |
@@ -253,8 +228,8 @@ delta = 15 * 60 | |||
253 | -- | Should maintain a set of stable long running nodes. | 228 | -- | Should maintain a set of stable long running nodes. |
254 | -- | 229 | -- |
255 | -- Note: pings are triggerd only when a bucket is full. | 230 | -- Note: pings are triggerd only when a bucket is full. |
256 | insertBucket :: (Eq ip, Alternative f) => Timestamp -> Event ip -> Bucket ip | 231 | insertBucket :: (Eq ip, Alternative f, Ord (NodeId dht)) => Timestamp -> Event dht ip u -> Bucket dht ip u |
257 | -> f ([CheckPing ip], Bucket ip) | 232 | -> f ([CheckPing dht ip u], Bucket dht ip u) |
258 | insertBucket curTime (TryInsert info) bucket | 233 | insertBucket curTime (TryInsert info) bucket |
259 | -- just update timestamp if a node is already in bucket | 234 | -- just update timestamp if a node is already in bucket |
260 | | already_have | 235 | | already_have |
@@ -305,7 +280,9 @@ insertBucket curTime (PingResult bad_node got_response) bucket | |||
305 | pure $ PSQ.insert info curTime nodes' | 280 | pure $ PSQ.insert info curTime nodes' |
306 | | otherwise = id | 281 | | otherwise = id |
307 | 282 | ||
308 | updateStamps :: Eq ip => Timestamp -> [NodeInfo KMessageOf ip ()] -> PSQ (NodeInfo KMessageOf ip ()) Timestamp -> PSQ (NodeInfo KMessageOf ip ()) Timestamp | 283 | updateStamps :: ( Eq ip |
284 | , Ord (NodeId dht) | ||
285 | ) => Timestamp -> [NodeInfo dht ip u] -> PSQ (NodeInfo dht ip u) Timestamp -> PSQ (NodeInfo dht ip u) Timestamp | ||
309 | updateStamps curTime stales nodes = foldl' (\q n -> PSQ.insert n curTime q) nodes stales | 286 | updateStamps curTime stales nodes = foldl' (\q n -> PSQ.insert n curTime q) nodes stales |
310 | 287 | ||
311 | 288 | ||
@@ -327,7 +304,11 @@ partitionQ imp test q0 = do | |||
327 | select f = if test e then \(a,b) -> flip (,) b <$> f a | 304 | select f = if test e then \(a,b) -> flip (,) b <$> f a |
328 | else \(a,b) -> (,) a <$> f b | 305 | else \(a,b) -> (,) a <$> f b |
329 | 306 | ||
330 | split :: Eq ip => BitIx -> Bucket ip -> (Bucket ip, Bucket ip) | 307 | split :: forall dht ip u. |
308 | ( Eq ip | ||
309 | , Ord (NodeId dht) | ||
310 | , FiniteBits (NodeId dht) | ||
311 | ) => BitIx -> Bucket dht ip u -> (Bucket dht ip u, Bucket dht ip u) | ||
331 | split i b = (Bucket ns qs, Bucket ms rs) | 312 | split i b = (Bucket ns qs, Bucket ms rs) |
332 | where | 313 | where |
333 | (ns,ms) = (PSQ.fromList *** PSQ.fromList) . partition (spanBit . key) . PSQ.toList $ bktNodes b | 314 | (ns,ms) = (PSQ.fromList *** PSQ.fromList) . partition (spanBit . key) . PSQ.toList $ bktNodes b |
@@ -337,7 +318,7 @@ split i b = (Bucket ns qs, Bucket ms rs) | |||
337 | FiniteBits (Network.RPC.NodeId dht) => | 318 | FiniteBits (Network.RPC.NodeId dht) => |
338 | NodeInfo dht addr u -> Bool | 319 | NodeInfo dht addr u -> Bool |
339 | -} | 320 | -} |
340 | spanBit :: NodeInfo KMessageOf addr () -> Bool | 321 | spanBit :: NodeInfo dht addr u -> Bool |
341 | spanBit entry = testIdBit (nodeId entry) i | 322 | spanBit entry = testIdBit (nodeId entry) i |
342 | 323 | ||
343 | {----------------------------------------------------------------------- | 324 | {----------------------------------------------------------------------- |
@@ -350,12 +331,15 @@ type BucketCount = Int | |||
350 | defaultBucketCount :: BucketCount | 331 | defaultBucketCount :: BucketCount |
351 | defaultBucketCount = 20 | 332 | defaultBucketCount = 20 |
352 | 333 | ||
353 | data Info ip = Info | 334 | data Info dht ip u = Info |
354 | { myBuckets :: Table ip | 335 | { myBuckets :: Table dht ip u |
355 | , myNodeId :: NodeId | 336 | , myNodeId :: NodeId dht |
356 | , myAddress :: SockAddr | 337 | , myAddress :: SockAddr |
357 | } | 338 | } |
358 | deriving (Eq, Show, Generic) | 339 | deriving Generic |
340 | |||
341 | deriving instance (Eq ip, Eq u, Eq (NodeId dht)) => Eq (Info dht ip u) | ||
342 | deriving instance (Show ip, Show u, Show (NodeId dht)) => Show (Info dht ip u) | ||
359 | 343 | ||
360 | -- instance (Eq ip, Serialize ip) => Serialize (Info ip) | 344 | -- instance (Eq ip, Serialize ip) => Serialize (Info ip) |
361 | 345 | ||
@@ -375,31 +359,33 @@ data Info ip = Info | |||
375 | -- is always split into two new buckets covering the ranges @0..2 ^ | 359 | -- is always split into two new buckets covering the ranges @0..2 ^ |
376 | -- 159@ and @2 ^ 159..2 ^ 160@. | 360 | -- 159@ and @2 ^ 159..2 ^ 160@. |
377 | -- | 361 | -- |
378 | data Table ip | 362 | data Table dht ip u |
379 | -- most nearest bucket | 363 | -- most nearest bucket |
380 | = Tip NodeId BucketCount (Bucket ip) | 364 | = Tip (NodeId dht) BucketCount (Bucket dht ip u) |
381 | 365 | ||
382 | -- left biased tree branch | 366 | -- left biased tree branch |
383 | | Zero (Table ip) (Bucket ip) | 367 | | Zero (Table dht ip u) (Bucket dht ip u) |
384 | 368 | ||
385 | -- right biased tree branch | 369 | -- right biased tree branch |
386 | | One (Bucket ip) (Table ip) | 370 | | One (Bucket dht ip u) (Table dht ip u) |
387 | deriving (Show, Generic) | 371 | deriving Generic |
388 | 372 | ||
389 | instance Eq ip => Eq (Table ip) where | 373 | instance (Eq ip, Eq (NodeId dht)) => Eq (Table dht ip u) where |
390 | (==) = (==) `on` Network.BitTorrent.DHT.Routing.toList | 374 | (==) = (==) `on` Network.BitTorrent.DHT.Routing.toList |
391 | 375 | ||
392 | instance Serialize NominalDiffTime where | 376 | instance Serialize NominalDiffTime where |
393 | put = putWord32be . fromIntegral . fromEnum | 377 | put = putWord32be . fromIntegral . fromEnum |
394 | get = (toEnum . fromIntegral) <$> getWord32be | 378 | get = (toEnum . fromIntegral) <$> getWord32be |
395 | 379 | ||
380 | deriving instance (Show ip, Show u, Show (NodeId dht)) => Show (Table dht ip u) | ||
381 | |||
396 | -- | Normally, routing table should be saved between invocations of | 382 | -- | Normally, routing table should be saved between invocations of |
397 | -- the client software. Note that you don't need to store /this/ | 383 | -- the client software. Note that you don't need to store /this/ |
398 | -- 'NodeId' since it is already included in routing table. | 384 | -- 'NodeId' since it is already included in routing table. |
399 | instance (Eq ip, Serialize ip) => Serialize (Table ip) | 385 | instance (Eq ip, Serialize ip, Ord (NodeId dht), Serialize (NodeId dht), Serialize u) => Serialize (Table dht ip u) |
400 | 386 | ||
401 | -- | Shape of the table. | 387 | -- | Shape of the table. |
402 | instance Pretty (Table ip) where | 388 | instance Pretty (Table dht ip u) where |
403 | pPrint t | 389 | pPrint t |
404 | | bucketCount < 6 = hcat $ punctuate ", " $ L.map PP.int ss | 390 | | bucketCount < 6 = hcat $ punctuate ", " $ L.map PP.int ss |
405 | | otherwise = brackets $ | 391 | | otherwise = brackets $ |
@@ -410,26 +396,26 @@ instance Pretty (Table ip) where | |||
410 | ss = shape t | 396 | ss = shape t |
411 | 397 | ||
412 | -- | Empty table with specified /spine/ node id. | 398 | -- | Empty table with specified /spine/ node id. |
413 | nullTable :: Eq ip => NodeId -> BucketCount -> Table ip | 399 | nullTable :: Eq ip => NodeId dht -> BucketCount -> Table dht ip u |
414 | nullTable nid n = Tip nid (bucketCount (pred n)) (Bucket PSQ.empty (runIdentity $ emptyQueue bucketQ)) | 400 | nullTable nid n = Tip nid (bucketCount (pred n)) (Bucket PSQ.empty (runIdentity $ emptyQueue bucketQ)) |
415 | where | 401 | where |
416 | bucketCount x = max 0 (min 159 x) | 402 | bucketCount x = max 0 (min 159 x) |
417 | 403 | ||
418 | -- | Test if table is empty. In this case DHT should start | 404 | -- | Test if table is empty. In this case DHT should start |
419 | -- bootstrapping process until table becomes 'full'. | 405 | -- bootstrapping process until table becomes 'full'. |
420 | null :: Table ip -> Bool | 406 | null :: Table dht ip u -> Bool |
421 | null (Tip _ _ b) = PSQ.null $ bktNodes b | 407 | null (Tip _ _ b) = PSQ.null $ bktNodes b |
422 | null _ = False | 408 | null _ = False |
423 | 409 | ||
424 | -- | Test if table have maximum number of nodes. No more nodes can be | 410 | -- | Test if table have maximum number of nodes. No more nodes can be |
425 | -- 'insert'ed, except old ones becomes bad. | 411 | -- 'insert'ed, except old ones becomes bad. |
426 | full :: Table ip -> Bool | 412 | full :: Table dht ip u -> Bool |
427 | full (Tip _ n _) = n == 0 | 413 | full (Tip _ n _) = n == 0 |
428 | full (Zero t b) = PSQ.size (bktNodes b) == defaultBucketSize && full t | 414 | full (Zero t b) = PSQ.size (bktNodes b) == defaultBucketSize && full t |
429 | full (One b t) = PSQ.size (bktNodes b) == defaultBucketSize && full t | 415 | full (One b t) = PSQ.size (bktNodes b) == defaultBucketSize && full t |
430 | 416 | ||
431 | -- | Get the /spine/ node id. | 417 | -- | Get the /spine/ node id. |
432 | thisId :: Table ip -> NodeId | 418 | thisId :: Table dht ip u -> NodeId dht |
433 | thisId (Tip nid _ _) = nid | 419 | thisId (Tip nid _ _) = nid |
434 | thisId (Zero table _) = thisId table | 420 | thisId (Zero table _) = thisId table |
435 | thisId (One _ table) = thisId table | 421 | thisId (One _ table) = thisId table |
@@ -439,18 +425,19 @@ type NodeCount = Int | |||
439 | 425 | ||
440 | -- | Internally, routing table is similar to list of buckets or a | 426 | -- | Internally, routing table is similar to list of buckets or a |
441 | -- /matrix/ of nodes. This function returns the shape of the matrix. | 427 | -- /matrix/ of nodes. This function returns the shape of the matrix. |
442 | shape :: Table ip -> [BucketSize] | 428 | shape :: Table dht ip u -> [BucketSize] |
443 | shape = map (PSQ.size . bktNodes) . toBucketList | 429 | shape = map (PSQ.size . bktNodes) . toBucketList |
444 | 430 | ||
445 | -- | Get number of nodes in the table. | 431 | -- | Get number of nodes in the table. |
446 | size :: Table ip -> NodeCount | 432 | size :: Table dht ip u -> NodeCount |
447 | size = L.sum . shape | 433 | size = L.sum . shape |
448 | 434 | ||
449 | -- | Get number of buckets in the table. | 435 | -- | Get number of buckets in the table. |
450 | depth :: Table ip -> BucketCount | 436 | depth :: Table dht ip u -> BucketCount |
451 | depth = L.length . shape | 437 | depth = L.length . shape |
452 | 438 | ||
453 | lookupBucket :: NodeId -> Table ip -> [Bucket ip] | 439 | lookupBucket :: ( FiniteBits (NodeId dht) |
440 | ) => NodeId dht -> Table dht ip u -> [Bucket dht ip u] | ||
454 | lookupBucket nid = go 0 [] | 441 | lookupBucket nid = go 0 [] |
455 | where | 442 | where |
456 | go i bs (Zero table bucket) | 443 | go i bs (Zero table bucket) |
@@ -461,14 +448,18 @@ lookupBucket nid = go 0 [] | |||
461 | | otherwise = bucket : toBucketList table ++ bs | 448 | | otherwise = bucket : toBucketList table ++ bs |
462 | go _ bs (Tip _ _ bucket) = bucket : bs | 449 | go _ bs (Tip _ _ bucket) = bucket : bs |
463 | 450 | ||
464 | compatibleNodeId :: Table ip -> IO NodeId | 451 | compatibleNodeId :: forall dht ip u. |
452 | ( Serialize (NodeId dht) | ||
453 | , FiniteBits (NodeId dht) | ||
454 | ) => Table dht ip u -> IO (NodeId dht) | ||
465 | compatibleNodeId tbl = genBucketSample prefix br | 455 | compatibleNodeId tbl = genBucketSample prefix br |
466 | where | 456 | where |
467 | br = bucketRange (L.length (shape tbl) - 1) True | 457 | br = bucketRange (L.length (shape tbl) - 1) True |
458 | nodeIdSize = finiteBitSize (undefined :: NodeId dht) `div` 8 | ||
468 | bs = BS.pack $ take nodeIdSize $ tablePrefix tbl ++ repeat 0 | 459 | bs = BS.pack $ take nodeIdSize $ tablePrefix tbl ++ repeat 0 |
469 | prefix = either error id $ S.decode bs | 460 | prefix = either error id $ S.decode bs |
470 | 461 | ||
471 | tablePrefix :: Table ip -> [Word8] | 462 | tablePrefix :: Table dht ip u -> [Word8] |
472 | tablePrefix = map (packByte . take 8 . (++repeat False)) | 463 | tablePrefix = map (packByte . take 8 . (++repeat False)) |
473 | . chunksOf 8 | 464 | . chunksOf 8 |
474 | . tableBits | 465 | . tableBits |
@@ -477,7 +468,7 @@ tablePrefix = map (packByte . take 8 . (++repeat False)) | |||
477 | bitmask ix True = bit ix | 468 | bitmask ix True = bit ix |
478 | bitmask _ _ = 0 | 469 | bitmask _ _ = 0 |
479 | 470 | ||
480 | tableBits :: Table ip -> [Bool] | 471 | tableBits :: Table dht ip u -> [Bool] |
481 | tableBits (One _ tbl) = True : tableBits tbl | 472 | tableBits (One _ tbl) = True : tableBits tbl |
482 | tableBits (Zero tbl _) = False : tableBits tbl | 473 | tableBits (Zero tbl _) = False : tableBits tbl |
483 | tableBits (Tip _ _ _) = [] | 474 | tableBits (Tip _ _ _) = [] |
@@ -498,20 +489,23 @@ type K = Int | |||
498 | defaultK :: K | 489 | defaultK :: K |
499 | defaultK = 8 | 490 | defaultK = 8 |
500 | 491 | ||
501 | class TableKey k where | 492 | class TableKey dht k where |
502 | toNodeId :: k -> NodeId | 493 | toNodeId :: k -> NodeId dht |
503 | 494 | ||
504 | instance TableKey NodeId where | 495 | instance TableKey dht (NodeId dht) where |
505 | toNodeId = id | 496 | toNodeId = id |
506 | 497 | ||
507 | instance TableKey InfoHash where | 498 | instance TableKey KMessageOf InfoHash where |
508 | toNodeId = either (error msg) id . S.decode . S.encode | 499 | toNodeId = either (error msg) id . S.decode . S.encode |
509 | where -- TODO unsafe coerse? | 500 | where -- TODO unsafe coerse? |
510 | msg = "tableKey: impossible" | 501 | msg = "tableKey: impossible" |
511 | 502 | ||
512 | -- | Get a list of /K/ closest nodes using XOR metric. Used in | 503 | -- | Get a list of /K/ closest nodes using XOR metric. Used in |
513 | -- 'find_node' and 'get_peers' queries. | 504 | -- 'find_node' and 'get_peers' queries. |
514 | kclosest :: Eq ip => TableKey a => K -> a -> Table ip -> [NodeInfo KMessageOf ip ()] | 505 | kclosest :: ( Eq ip |
506 | , Ord (NodeId dht) | ||
507 | , FiniteBits (NodeId dht) | ||
508 | ) => TableKey dht a => K -> a -> Table dht ip u -> [NodeInfo dht ip u] | ||
515 | kclosest k (toNodeId -> nid) tbl = take k $ rank nodeId nid (L.concat bucket) | 509 | kclosest k (toNodeId -> nid) tbl = take k $ rank nodeId nid (L.concat bucket) |
516 | ++ rank nodeId nid (L.concat everyone) | 510 | ++ rank nodeId nid (L.concat everyone) |
517 | where | 511 | where |
@@ -525,7 +519,10 @@ kclosest k (toNodeId -> nid) tbl = take k $ rank nodeId nid (L.concat bucket) | |||
525 | -- Routing | 519 | -- Routing |
526 | -----------------------------------------------------------------------} | 520 | -----------------------------------------------------------------------} |
527 | 521 | ||
528 | splitTip :: Eq ip => NodeId -> BucketCount -> BitIx -> Bucket ip -> Table ip | 522 | splitTip :: ( Eq ip |
523 | , Ord (NodeId dht) | ||
524 | , FiniteBits (NodeId dht) | ||
525 | ) => NodeId dht -> BucketCount -> BitIx -> Bucket dht ip u -> Table dht ip u | ||
529 | splitTip nid n i bucket | 526 | splitTip nid n i bucket |
530 | | testIdBit nid i = (One zeros (Tip nid (pred n) ones)) | 527 | | testIdBit nid i = (One zeros (Tip nid (pred n) ones)) |
531 | | otherwise = (Zero (Tip nid (pred n) zeros) ones) | 528 | | otherwise = (Zero (Tip nid (pred n) zeros) ones) |
@@ -538,11 +535,15 @@ splitTip nid n i bucket | |||
538 | -- k nodes in them. Which subtrees I mean is illustrated in Fig 1. of Kademlia | 535 | -- k nodes in them. Which subtrees I mean is illustrated in Fig 1. of Kademlia |
539 | -- paper. The rule requiring additional splits is in section 2.4. | 536 | -- paper. The rule requiring additional splits is in section 2.4. |
540 | modifyBucket | 537 | modifyBucket |
541 | :: forall ip xs. (Eq ip) => | 538 | :: forall xs dht ip u. |
542 | NodeId -> (Bucket ip -> Maybe (xs, Bucket ip)) -> Table ip -> Maybe (xs,Table ip) | 539 | ( Eq ip |
540 | , Ord (NodeId dht) | ||
541 | , FiniteBits (NodeId dht) | ||
542 | ) => | ||
543 | NodeId dht -> (Bucket dht ip u -> Maybe (xs, Bucket dht ip u)) -> Table dht ip u -> Maybe (xs,Table dht ip u) | ||
543 | modifyBucket nodeId f = go (0 :: BitIx) | 544 | modifyBucket nodeId f = go (0 :: BitIx) |
544 | where | 545 | where |
545 | go :: BitIx -> Table ip -> Maybe (xs, Table ip) | 546 | go :: BitIx -> Table dht ip u -> Maybe (xs, Table dht ip u) |
546 | go !i (Zero table bucket) | 547 | go !i (Zero table bucket) |
547 | | testIdBit nodeId i = second (Zero table) <$> f bucket | 548 | | testIdBit nodeId i = second (Zero table) <$> f bucket |
548 | | otherwise = second (`Zero` bucket) <$> go (succ i) table | 549 | | otherwise = second (`Zero` bucket) <$> go (succ i) table |
@@ -555,23 +556,36 @@ modifyBucket nodeId f = go (0 :: BitIx) | |||
555 | <|> go i (splitTip nid n i bucket) | 556 | <|> go i (splitTip nid n i bucket) |
556 | 557 | ||
557 | -- | Triggering event for atomic table update | 558 | -- | Triggering event for atomic table update |
558 | data Event ip = TryInsert { foreignNode :: NodeInfo KMessageOf ip () } | 559 | data Event dht ip u = TryInsert { foreignNode :: NodeInfo dht ip u } |
559 | | PingResult { foreignNode :: NodeInfo KMessageOf ip () | 560 | | PingResult { foreignNode :: NodeInfo dht ip u |
560 | , ponged :: Bool | 561 | , ponged :: Bool |
561 | } | 562 | } |
562 | deriving (Eq,Show) -- Ord | 563 | deriving instance Eq (NodeId dht) => Eq (Event dht ip u) |
563 | 564 | deriving instance ( Show ip | |
564 | eventId :: Event ip -> NodeId | 565 | , Show (NodeId dht) |
566 | , Show u | ||
567 | ) => Show (Event dht ip u) | ||
568 | |||
569 | eventId :: Event dht ip u -> NodeId dht | ||
565 | eventId (TryInsert NodeInfo{..}) = nodeId | 570 | eventId (TryInsert NodeInfo{..}) = nodeId |
566 | eventId (PingResult NodeInfo{..} _) = nodeId | 571 | eventId (PingResult NodeInfo{..} _) = nodeId |
567 | 572 | ||
568 | -- | Actions requested by atomic table update | 573 | -- | Actions requested by atomic table update |
569 | data CheckPing ip = CheckPing [NodeInfo KMessageOf ip ()] | 574 | data CheckPing dht ip u = CheckPing [NodeInfo dht ip u] |
570 | deriving (Eq,Show) -- Ord | 575 | |
576 | deriving instance Eq (NodeId dht) => Eq (CheckPing dht ip u) | ||
577 | deriving instance ( Show ip | ||
578 | , Show (NodeId dht) | ||
579 | , Show u | ||
580 | ) => Show (CheckPing dht ip u) | ||
571 | 581 | ||
572 | 582 | ||
573 | -- | Atomic 'Table' update | 583 | -- | Atomic 'Table' update |
574 | insert :: (Eq ip, Applicative m) => Timestamp -> Event ip -> Table ip -> m ([CheckPing ip], Table ip) | 584 | insert :: ( Eq ip |
585 | , Applicative m | ||
586 | , Ord (NodeId dht) | ||
587 | , FiniteBits (NodeId dht) | ||
588 | ) => Timestamp -> Event dht ip u -> Table dht ip u -> m ([CheckPing dht ip u], Table dht ip u) | ||
575 | insert tm event tbl = pure $ fromMaybe ([],tbl) $ modifyBucket (eventId event) (insertBucket tm event) tbl | 589 | insert tm event tbl = pure $ fromMaybe ([],tbl) $ modifyBucket (eventId event) (insertBucket tm event) tbl |
576 | 590 | ||
577 | 591 | ||
@@ -579,16 +593,16 @@ insert tm event tbl = pure $ fromMaybe ([],tbl) $ modifyBucket (eventId event) ( | |||
579 | -- Conversion | 593 | -- Conversion |
580 | -----------------------------------------------------------------------} | 594 | -----------------------------------------------------------------------} |
581 | 595 | ||
582 | type TableEntry ip = (NodeInfo KMessageOf ip (), Timestamp) | 596 | type TableEntry dht ip u = (NodeInfo dht ip u, Timestamp) |
583 | 597 | ||
584 | tableEntry :: NodeEntry ip -> TableEntry ip | 598 | tableEntry :: NodeEntry dht ip u -> TableEntry dht ip u |
585 | tableEntry (a :-> b) = (a, b) | 599 | tableEntry (a :-> b) = (a, b) |
586 | 600 | ||
587 | -- | Non-empty list of buckets. | 601 | -- | Non-empty list of buckets. |
588 | toBucketList :: Table ip -> [Bucket ip] | 602 | toBucketList :: Table dht ip u -> [Bucket dht ip u] |
589 | toBucketList (Tip _ _ b) = [b] | 603 | toBucketList (Tip _ _ b) = [b] |
590 | toBucketList (Zero t b) = b : toBucketList t | 604 | toBucketList (Zero t b) = b : toBucketList t |
591 | toBucketList (One b t) = b : toBucketList t | 605 | toBucketList (One b t) = b : toBucketList t |
592 | 606 | ||
593 | toList :: Eq ip => Table ip -> [[TableEntry ip]] | 607 | toList :: Eq ip => Table dht ip u -> [[TableEntry dht ip u]] |
594 | toList = L.map (L.map tableEntry . PSQ.toList . bktNodes) . toBucketList | 608 | toList = L.map (L.map tableEntry . PSQ.toList . bktNodes) . toBucketList |
diff --git a/src/Network/BitTorrent/DHT/Search.hs b/src/Network/BitTorrent/DHT/Search.hs index 854f26c7..844b4575 100644 --- a/src/Network/BitTorrent/DHT/Search.hs +++ b/src/Network/BitTorrent/DHT/Search.hs | |||
@@ -1,3 +1,4 @@ | |||
1 | {-# LANGUAGE CPP #-} | ||
1 | {-# LANGUAGE PatternSynonyms #-} | 2 | {-# LANGUAGE PatternSynonyms #-} |
2 | {-# LANGUAGE RecordWildCards #-} | 3 | {-# LANGUAGE RecordWildCards #-} |
3 | {-# LANGUAGE ScopedTypeVariables #-} | 4 | {-# LANGUAGE ScopedTypeVariables #-} |
@@ -24,21 +25,28 @@ import qualified Data.Wrapper.PSQ as PSQ | |||
24 | ;import Data.Wrapper.PSQ (pattern (:->), Binding, PSQ) | 25 | ;import Data.Wrapper.PSQ (pattern (:->), Binding, PSQ) |
25 | import Network.BitTorrent.Address hiding (NodeId) | 26 | import Network.BitTorrent.Address hiding (NodeId) |
26 | import Network.RPC | 27 | import Network.RPC |
27 | import Network.KRPC.Message (KMessageOf) | 28 | #ifdef VERSION_bencoding |
28 | import Network.DHT.Mainline () | 29 | import Network.DHT.Mainline () |
30 | import Network.KRPC.Message (KMessageOf) | ||
31 | type Ann = () | ||
32 | #else | ||
33 | import Data.Tox as Tox | ||
34 | type KMessageOf = Tox.Message | ||
35 | type Ann = Bool | ||
36 | #endif | ||
29 | 37 | ||
30 | data IterativeSearch ip r = IterativeSearch | 38 | data IterativeSearch ip r = IterativeSearch |
31 | { searchTarget :: NodeId KMessageOf | 39 | { searchTarget :: NodeId KMessageOf |
32 | , searchQuery :: NodeInfo KMessageOf ip () -> IO ([NodeInfo KMessageOf ip ()], [r]) | 40 | , searchQuery :: NodeInfo KMessageOf ip Ann -> IO ([NodeInfo KMessageOf ip Ann], [r]) |
33 | , searchPendingCount :: TVar Int | 41 | , searchPendingCount :: TVar Int |
34 | , searchQueued :: TVar (MinMaxPSQ (NodeInfo KMessageOf ip ()) (NodeDistance (NodeId KMessageOf))) | 42 | , searchQueued :: TVar (MinMaxPSQ (NodeInfo KMessageOf ip Ann) (NodeDistance (NodeId KMessageOf))) |
35 | , searchInformant :: TVar (MinMaxPSQ (NodeInfo KMessageOf ip ()) (NodeDistance (NodeId KMessageOf))) | 43 | , searchInformant :: TVar (MinMaxPSQ (NodeInfo KMessageOf ip Ann) (NodeDistance (NodeId KMessageOf))) |
36 | , searchVisited :: TVar (Set (NodeAddr ip)) | 44 | , searchVisited :: TVar (Set (NodeAddr ip)) |
37 | , searchResults :: TVar (Set r) | 45 | , searchResults :: TVar (Set r) |
38 | } | 46 | } |
39 | 47 | ||
40 | newSearch :: Eq ip => (NodeInfo KMessageOf ip () -> IO ([NodeInfo KMessageOf ip ()], [r])) | 48 | newSearch :: Eq ip => (NodeInfo KMessageOf ip Ann -> IO ([NodeInfo KMessageOf ip Ann], [r])) |
41 | -> NodeId KMessageOf -> [NodeInfo KMessageOf ip ()] -> IO (IterativeSearch ip r) | 49 | -> NodeId KMessageOf -> [NodeInfo KMessageOf ip Ann] -> IO (IterativeSearch ip r) |
42 | newSearch qry target ns = atomically $ do | 50 | newSearch qry target ns = atomically $ do |
43 | c <- newTVar 0 | 51 | c <- newTVar 0 |
44 | q <- newTVar $ MM.fromList $ map (\n -> n :-> distance target (nodeId n)) ns | 52 | q <- newTVar $ MM.fromList $ map (\n -> n :-> distance target (nodeId n)) ns |
@@ -55,7 +63,7 @@ searchK = 8 | |||
55 | 63 | ||
56 | sendQuery :: forall a ip. (Ord a, Ord ip) => | 64 | sendQuery :: forall a ip. (Ord a, Ord ip) => |
57 | IterativeSearch ip a | 65 | IterativeSearch ip a |
58 | -> Binding (NodeInfo KMessageOf ip ()) (NodeDistance (NodeId KMessageOf)) | 66 | -> Binding (NodeInfo KMessageOf ip Ann) (NodeDistance (NodeId KMessageOf)) |
59 | -> IO () | 67 | -> IO () |
60 | sendQuery IterativeSearch{..} (ni :-> d) = do | 68 | sendQuery IterativeSearch{..} (ni :-> d) = do |
61 | (ns,rs) <- handle (\(SomeException e) -> return ([],[])) | 69 | (ns,rs) <- handle (\(SomeException e) -> return ([],[])) |
diff --git a/src/Network/BitTorrent/DHT/Session.hs b/src/Network/BitTorrent/DHT/Session.hs index aa6ee396..bec2dabc 100644 --- a/src/Network/BitTorrent/DHT/Session.hs +++ b/src/Network/BitTorrent/DHT/Session.hs | |||
@@ -106,9 +106,11 @@ import Data.Serialize as S | |||
106 | import Data.Torrent as Torrent | 106 | import Data.Torrent as Torrent |
107 | import Network.KRPC as KRPC hiding (Options, def) | 107 | import Network.KRPC as KRPC hiding (Options, def) |
108 | import qualified Network.KRPC as KRPC (def) | 108 | import qualified Network.KRPC as KRPC (def) |
109 | import Network.KRPC.Message (KMessageOf) | ||
110 | #ifdef VERSION_bencoding | 109 | #ifdef VERSION_bencoding |
111 | import Data.BEncode (BValue) | 110 | import Data.BEncode (BValue) |
111 | import Network.KRPC.Message (KMessageOf) | ||
112 | #else | ||
113 | import Data.Tox as Tox | ||
112 | #endif | 114 | #endif |
113 | import Network.BitTorrent.Address | 115 | import Network.BitTorrent.Address |
114 | import Network.BitTorrent.DHT.ContactInfo (PeerStore) | 116 | import Network.BitTorrent.DHT.ContactInfo (PeerStore) |
@@ -257,11 +259,19 @@ data Node ip = Node | |||
257 | 259 | ||
258 | -- | Pseudo-unique self-assigned session identifier. This value is | 260 | -- | Pseudo-unique self-assigned session identifier. This value is |
259 | -- constant during DHT session and (optionally) between sessions. | 261 | -- constant during DHT session and (optionally) between sessions. |
260 | , tentativeNodeId :: !NodeId | 262 | #ifdef VERSION_bencoding |
263 | , tentativeNodeId :: !(NodeId KMessageOf) | ||
264 | #else | ||
265 | , tentativeNodeId :: !(NodeId Tox.Message) | ||
266 | #endif | ||
261 | 267 | ||
262 | , resources :: !InternalState | 268 | , resources :: !InternalState |
263 | , manager :: !(Manager (DHT ip )) -- ^ RPC manager; | 269 | , manager :: !(Manager (DHT ip )) -- ^ RPC manager; |
264 | , routingInfo :: !(TVar (Maybe (R.Info ip))) -- ^ search table; | 270 | #ifdef VERSION_bencoding |
271 | , routingInfo :: !(TVar (Maybe (R.Info KMessageOf ip ()))) -- ^ search table; | ||
272 | #else | ||
273 | , routingInfo :: !(TVar (Maybe (R.Info Tox.Message ip Bool))) -- ^ search table; | ||
274 | #endif | ||
265 | , contactInfo :: !(TVar (PeerStore ip )) -- ^ published by other nodes; | 275 | , contactInfo :: !(TVar (PeerStore ip )) -- ^ published by other nodes; |
266 | , announceInfo :: !(TVar AnnounceSet ) -- ^ to publish by this node; | 276 | , announceInfo :: !(TVar AnnounceSet ) -- ^ to publish by this node; |
267 | , sessionTokens :: !(TVar SessionTokens ) -- ^ query session IDs. | 277 | , sessionTokens :: !(TVar SessionTokens ) -- ^ query session IDs. |
@@ -319,7 +329,7 @@ instance MonadLogger (DHT ip) where | |||
319 | #ifdef VERSION_bencoding | 329 | #ifdef VERSION_bencoding |
320 | type NodeHandler ip = Handler (DHT ip) KMessageOf BValue | 330 | type NodeHandler ip = Handler (DHT ip) KMessageOf BValue |
321 | #else | 331 | #else |
322 | type NodeHandler ip = Handler (DHT ip) KMessageOf ByteString | 332 | type NodeHandler ip = Handler (DHT ip) Tox.Message ByteString |
323 | #endif | 333 | #endif |
324 | 334 | ||
325 | -- | Run DHT session. You /must/ properly close session using | 335 | -- | Run DHT session. You /must/ properly close session using |
@@ -330,7 +340,11 @@ newNode :: Address ip | |||
330 | -> Options -- ^ various dht options; | 340 | -> Options -- ^ various dht options; |
331 | -> NodeAddr ip -- ^ node address to bind; | 341 | -> NodeAddr ip -- ^ node address to bind; |
332 | -> LogFun -- ^ | 342 | -> LogFun -- ^ |
333 | -> Maybe NodeId -- ^ use this NodeId, if not given a new one is generated. | 343 | #ifdef VERSION_bencoding |
344 | -> Maybe (NodeId KMessageOf) -- ^ use this NodeId, if not given a new one is generated. | ||
345 | #else | ||
346 | -> Maybe (NodeId Tox.Message) -- ^ use this NodeId, if not given a new one is generated. | ||
347 | #endif | ||
334 | -> IO (Node ip) -- ^ a new DHT node running at given address. | 348 | -> IO (Node ip) -- ^ a new DHT node running at given address. |
335 | newNode hs opts naddr logger mbid = do | 349 | newNode hs opts naddr logger mbid = do |
336 | s <- createInternalState | 350 | s <- createInternalState |
@@ -406,7 +420,11 @@ routableAddress = do | |||
406 | return $ myAddress <$> info | 420 | return $ myAddress <$> info |
407 | 421 | ||
408 | -- | The current NodeId that the given remote node should know us by. | 422 | -- | The current NodeId that the given remote node should know us by. |
409 | myNodeIdAccordingTo :: NodeAddr ip -> DHT ip NodeId | 423 | #ifdef VERSION_bencoding |
424 | myNodeIdAccordingTo :: NodeAddr ip -> DHT ip (NodeId KMessageOf) | ||
425 | #else | ||
426 | myNodeIdAccordingTo :: NodeAddr ip -> DHT ip (NodeId Tox.Message) | ||
427 | #endif | ||
410 | myNodeIdAccordingTo _ = do | 428 | myNodeIdAccordingTo _ = do |
411 | info <- asks routingInfo >>= liftIO . atomically . readTVar | 429 | info <- asks routingInfo >>= liftIO . atomically . readTVar |
412 | maybe (asks tentativeNodeId) | 430 | maybe (asks tentativeNodeId) |
@@ -415,7 +433,11 @@ myNodeIdAccordingTo _ = do | |||
415 | 433 | ||
416 | -- | Get current routing table. Normally you don't need to use this | 434 | -- | Get current routing table. Normally you don't need to use this |
417 | -- function, but it can be usefull for debugging and profiling purposes. | 435 | -- function, but it can be usefull for debugging and profiling purposes. |
418 | getTable :: Eq ip => DHT ip (Table ip) | 436 | #ifdef VERSION_bencoding |
437 | getTable :: Eq ip => DHT ip (Table KMessageOf ip ()) | ||
438 | #else | ||
439 | getTable :: Eq ip => DHT ip (Table Tox.Message ip Bool) | ||
440 | #endif | ||
419 | getTable = do | 441 | getTable = do |
420 | Node { tentativeNodeId = myId | 442 | Node { tentativeNodeId = myId |
421 | , routingInfo = var | 443 | , routingInfo = var |
@@ -452,7 +474,11 @@ allPeers ih = do | |||
452 | -- | 474 | -- |
453 | -- This operation used for 'find_nodes' query. | 475 | -- This operation used for 'find_nodes' query. |
454 | -- | 476 | -- |
455 | getClosest :: Eq ip => TableKey k => k -> DHT ip [NodeInfo KMessageOf ip ()] | 477 | #ifdef VERSION_bencoding |
478 | getClosest :: Eq ip => TableKey KMessageOf k => k -> DHT ip [NodeInfo KMessageOf ip ()] | ||
479 | #else | ||
480 | getClosest :: Eq ip => TableKey Tox.Message k => k -> DHT ip [NodeInfo Tox.Message ip Bool] | ||
481 | #endif | ||
456 | getClosest node = do | 482 | getClosest node = do |
457 | k <- asks (optK . options) | 483 | k <- asks (optK . options) |
458 | kclosest k node <$> getTable | 484 | kclosest k node <$> getTable |