diff options
-rw-r--r-- | examples/dhtd.hs | 12 | ||||
-rw-r--r-- | src/Network/BitTorrent/Address.hs | 7 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT.hs | 2 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/ContactInfo.hs | 58 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Message.hs | 12 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Query.hs | 12 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Routing.hs | 2 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Session.hs | 20 |
8 files changed, 93 insertions, 32 deletions
diff --git a/examples/dhtd.hs b/examples/dhtd.hs index 6bf48595..96c31dfe 100644 --- a/examples/dhtd.hs +++ b/examples/dhtd.hs | |||
@@ -111,7 +111,8 @@ hPutClient h s = hPutStr h (marshalForClient s) | |||
111 | clientSession :: Node IPv4 -> MVar () -> RestrictedSocket -> Int -> Handle -> IO () | 111 | clientSession :: Node IPv4 -> MVar () -> RestrictedSocket -> Int -> Handle -> IO () |
112 | clientSession st signalQuit sock n h = do | 112 | clientSession st signalQuit sock n h = do |
113 | line <- map toLower . dropWhile isSpace <$> hGetLine h | 113 | line <- map toLower . dropWhile isSpace <$> hGetLine h |
114 | let cmd action = action >> clientSession st signalQuit sock n h | 114 | let cmd0 action = action >> clientSession st signalQuit sock n h |
115 | cmd action = cmd0 $ join $ runDHT st action | ||
115 | case line of | 116 | case line of |
116 | 117 | ||
117 | "quit" -> hPutClient h "goodbye." >> hClose h | 118 | "quit" -> hPutClient h "goodbye." >> hClose h |
@@ -120,7 +121,7 @@ clientSession st signalQuit sock n h = do | |||
120 | hClose h | 121 | hClose h |
121 | putMVar signalQuit () | 122 | putMVar signalQuit () |
122 | 123 | ||
123 | "ls" -> cmd $ join $ runDHT st $ do | 124 | "ls" -> cmd $ do |
124 | tbl <- getTable | 125 | tbl <- getTable |
125 | t <- showTable | 126 | t <- showTable |
126 | me <- myNodeIdAccordingTo (read "8.8.8.8:6881") | 127 | me <- myNodeIdAccordingTo (read "8.8.8.8:6881") |
@@ -133,8 +134,13 @@ clientSession st signalQuit sock n h = do | |||
133 | , ("internet address", show ip) | 134 | , ("internet address", show ip) |
134 | , ("buckets", show $ R.shape tbl)] | 135 | , ("buckets", show $ R.shape tbl)] |
135 | ] | 136 | ] |
137 | "swarms" -> cmd $ do | ||
138 | ss <- getSwarms | ||
139 | let r = map (\(h,c,n) -> (unwords [show h,show c], maybe "" show n)) ss | ||
140 | return $ do | ||
141 | hPutClient h $ showReport r | ||
136 | 142 | ||
137 | _ -> cmd $ hPutClient h "error." | 143 | _ -> cmd0 $ hPutClient h "error." |
138 | 144 | ||
139 | main :: IO () | 145 | main :: IO () |
140 | main = do | 146 | main = do |
diff --git a/src/Network/BitTorrent/Address.hs b/src/Network/BitTorrent/Address.hs index b4ce96b0..381ff50b 100644 --- a/src/Network/BitTorrent/Address.hs +++ b/src/Network/BitTorrent/Address.hs | |||
@@ -58,7 +58,8 @@ module Network.BitTorrent.Address | |||
58 | 58 | ||
59 | -- * Node | 59 | -- * Node |
60 | -- ** Id | 60 | -- ** Id |
61 | , NodeId(..) | 61 | , NodeId |
62 | , asNodeId | ||
62 | , nodeIdSize | 63 | , nodeIdSize |
63 | , testIdBit | 64 | , testIdBit |
64 | , NodeDistance | 65 | , NodeDistance |
@@ -646,6 +647,9 @@ newtype NodeId = NodeId ByteString | |||
646 | nodeIdSize :: Int | 647 | nodeIdSize :: Int |
647 | nodeIdSize = 20 | 648 | nodeIdSize = 20 |
648 | 649 | ||
650 | asNodeId :: ByteString -> NodeId | ||
651 | asNodeId bs = NodeId $ BS.take nodeIdSize bs | ||
652 | |||
649 | -- | Meaningless node id, for testing purposes only. | 653 | -- | Meaningless node id, for testing purposes only. |
650 | instance Default NodeId where | 654 | instance Default NodeId where |
651 | def = NodeId (BS.replicate nodeIdSize 0) | 655 | def = NodeId (BS.replicate nodeIdSize 0) |
@@ -801,6 +805,7 @@ data NodeInfo a = NodeInfo | |||
801 | , nodeAddr :: !(NodeAddr a) | 805 | , nodeAddr :: !(NodeAddr a) |
802 | } deriving (Show, Eq, Functor, Foldable, Traversable) | 806 | } deriving (Show, Eq, Functor, Foldable, Traversable) |
803 | 807 | ||
808 | |||
804 | instance Eq a => Ord (NodeInfo a) where | 809 | instance Eq a => Ord (NodeInfo a) where |
805 | compare = comparing nodeId | 810 | compare = comparing nodeId |
806 | 811 | ||
diff --git a/src/Network/BitTorrent/DHT.hs b/src/Network/BitTorrent/DHT.hs index 45c87831..aaa1cf33 100644 --- a/src/Network/BitTorrent/DHT.hs +++ b/src/Network/BitTorrent/DHT.hs | |||
@@ -87,7 +87,7 @@ fullLogging :: LogSource -> LogLevel -> Bool | |||
87 | fullLogging _ _ = True | 87 | fullLogging _ _ = True |
88 | 88 | ||
89 | -- | Run DHT on specified port. <add note about resources> | 89 | -- | Run DHT on specified port. <add note about resources> |
90 | dht :: Address ip | 90 | dht :: (Ord ip, Address ip) |
91 | => Options -- ^ normally you need to use 'Data.Default.def'; | 91 | => Options -- ^ normally you need to use 'Data.Default.def'; |
92 | -> NodeAddr ip -- ^ address to bind this node; | 92 | -> NodeAddr ip -- ^ address to bind this node; |
93 | -> (LogSource -> LogLevel -> Bool) -- ^ use 'fullLogging' as a noisy default | 93 | -> (LogSource -> LogLevel -> Bool) -- ^ use 'fullLogging' as a noisy default |
diff --git a/src/Network/BitTorrent/DHT/ContactInfo.hs b/src/Network/BitTorrent/DHT/ContactInfo.hs index d7c92e35..979dbb62 100644 --- a/src/Network/BitTorrent/DHT/ContactInfo.hs +++ b/src/Network/BitTorrent/DHT/ContactInfo.hs | |||
@@ -1,14 +1,19 @@ | |||
1 | module Network.BitTorrent.DHT.ContactInfo | 1 | module Network.BitTorrent.DHT.ContactInfo |
2 | ( PeerStore | 2 | ( PeerStore |
3 | , Network.BitTorrent.DHT.ContactInfo.lookup | 3 | , Network.BitTorrent.DHT.ContactInfo.lookup |
4 | , Network.BitTorrent.DHT.ContactInfo.insert | 4 | , Network.BitTorrent.DHT.ContactInfo.insertPeer |
5 | , knownSwarms | ||
5 | ) where | 6 | ) where |
6 | 7 | ||
8 | import Control.Applicative | ||
7 | import Data.Default | 9 | import Data.Default |
8 | import Data.List as L | 10 | import Data.List as L |
9 | import Data.Maybe | 11 | import Data.Maybe |
10 | import Data.HashMap.Strict as HM | 12 | import Data.HashMap.Strict as HM |
11 | import Data.Serialize | 13 | import Data.Serialize |
14 | import Data.PSQueue as PSQ | ||
15 | import Data.Time.Clock.POSIX | ||
16 | import Data.ByteString (ByteString) | ||
12 | 17 | ||
13 | import Data.Torrent | 18 | import Data.Torrent |
14 | import Network.BitTorrent.Address | 19 | import Network.BitTorrent.Address |
@@ -107,21 +112,43 @@ import Network.BitTorrent.Address | |||
107 | 112 | ||
108 | -- | Storage used to keep track a set of known peers in client, | 113 | -- | Storage used to keep track a set of known peers in client, |
109 | -- tracker or DHT sessions. | 114 | -- tracker or DHT sessions. |
110 | newtype PeerStore ip = PeerStore (HashMap InfoHash [PeerAddr ip]) | 115 | newtype PeerStore ip = PeerStore (HashMap InfoHash (SwarmData ip)) |
116 | |||
117 | type Timestamp = POSIXTime | ||
118 | |||
119 | data SwarmData ip = SwarmData | ||
120 | { peers :: PSQ (PeerAddr ip) Timestamp | ||
121 | , name :: Maybe ByteString | ||
122 | } | ||
123 | |||
124 | knownSwarms :: PeerStore ip -> [ (InfoHash, Int, Maybe ByteString) ] | ||
125 | knownSwarms (PeerStore m) = L.map (\(ih,SwarmData q n) -> (ih,PSQ.size q,n)) $ HM.toList m | ||
126 | |||
127 | swarmSinglton :: Ord ip => PeerAddr ip -> SwarmData ip | ||
128 | swarmSinglton a = SwarmData | ||
129 | { peers = PSQ.singleton a 0 | ||
130 | , name = Nothing } | ||
131 | |||
132 | swarmInsert :: Ord ip => SwarmData ip -> SwarmData ip -> SwarmData ip | ||
133 | swarmInsert old new = SwarmData | ||
134 | { peers = L.foldl' (\q (a :-> t) -> PSQ.insertWith (\p _ -> p) a t q) (peers old) (PSQ.toList $ peers new) | ||
135 | , name = name new <|> name old -- TODO: decodeUtf8' check | ||
136 | } | ||
137 | |||
111 | 138 | ||
112 | -- | Empty store. | 139 | -- | Empty store. |
113 | instance Default (PeerStore a) where | 140 | instance Default (PeerStore a) where |
114 | def = PeerStore HM.empty | 141 | def = PeerStore HM.empty |
115 | {-# INLINE def #-} | 142 | {-# INLINE def #-} |
116 | 143 | ||
117 | -- | Monoid under union operation. | 144 | -- -- | Monoid under union operation. |
118 | instance Eq a => Monoid (PeerStore a) where | 145 | -- instance Eq a => Monoid (PeerStore a) where |
119 | mempty = def | 146 | -- mempty = def |
120 | {-# INLINE mempty #-} | 147 | -- {-# INLINE mempty #-} |
121 | 148 | -- | |
122 | mappend (PeerStore a) (PeerStore b) = | 149 | -- mappend (PeerStore a) (PeerStore b) = |
123 | PeerStore (HM.unionWith L.union a b) | 150 | -- PeerStore (HM.unionWith L.union a b) |
124 | {-# INLINE mappend #-} | 151 | -- {-# INLINE mappend #-} |
125 | 152 | ||
126 | -- | Can be used to store peers between invocations of the client | 153 | -- | Can be used to store peers between invocations of the client |
127 | -- software. | 154 | -- software. |
@@ -130,9 +157,12 @@ instance Serialize (PeerStore a) where | |||
130 | put = undefined | 157 | put = undefined |
131 | 158 | ||
132 | -- | Used in 'get_peers' DHT queries. | 159 | -- | Used in 'get_peers' DHT queries. |
133 | lookup :: InfoHash -> PeerStore a -> [PeerAddr a] | 160 | lookup :: Ord a => InfoHash -> PeerStore a -> [PeerAddr a] |
134 | lookup ih (PeerStore m) = fromMaybe [] $ HM.lookup ih m | 161 | lookup ih (PeerStore m) = maybe [] (PSQ.keys . peers) $ HM.lookup ih m |
135 | 162 | ||
136 | -- | Used in 'announce_peer' DHT queries. | 163 | -- | Used in 'announce_peer' DHT queries. |
137 | insert :: Eq a => InfoHash -> PeerAddr a -> PeerStore a -> PeerStore a | 164 | insertPeer :: Ord a => InfoHash -> Maybe ByteString -> PeerAddr a -> PeerStore a -> PeerStore a |
138 | insert ih a (PeerStore m) = PeerStore (HM.insertWith L.union ih [a] m) | 165 | insertPeer ih name a (PeerStore m) = PeerStore (HM.insertWith swarmInsert ih a' m) |
166 | where | ||
167 | a' = SwarmData { peers = PSQ.singleton a 0 | ||
168 | , name = name } | ||
diff --git a/src/Network/BitTorrent/DHT/Message.hs b/src/Network/BitTorrent/DHT/Message.hs index 9d66741f..d31cce82 100644 --- a/src/Network/BitTorrent/DHT/Message.hs +++ b/src/Network/BitTorrent/DHT/Message.hs | |||
@@ -86,6 +86,7 @@ module Network.BitTorrent.DHT.Message | |||
86 | import Control.Applicative | 86 | import Control.Applicative |
87 | import Data.BEncode as BE | 87 | import Data.BEncode as BE |
88 | import Data.BEncode.BDict | 88 | import Data.BEncode.BDict |
89 | import Data.ByteString (ByteString) | ||
89 | import Data.List as L | 90 | import Data.List as L |
90 | import Data.Monoid | 91 | import Data.Monoid |
91 | import Data.Serialize as S | 92 | import Data.Serialize as S |
@@ -251,6 +252,9 @@ peers_key = "values" | |||
251 | token_key :: BKey | 252 | token_key :: BKey |
252 | token_key = "token" | 253 | token_key = "token" |
253 | 254 | ||
255 | name_key :: BKey | ||
256 | name_key = "name" | ||
257 | |||
254 | instance (Typeable ip, Serialize ip) => BEncode (GotPeers ip) where | 258 | instance (Typeable ip, Serialize ip) => BEncode (GotPeers ip) where |
255 | toBEncode GotPeers {..} = toDict $ | 259 | toBEncode GotPeers {..} = toDict $ |
256 | case peers of | 260 | case peers of |
@@ -295,11 +299,17 @@ data Announce = Announce | |||
295 | -- | infohash of the torrent; | 299 | -- | infohash of the torrent; |
296 | , topic :: InfoHash | 300 | , topic :: InfoHash |
297 | 301 | ||
302 | -- | some clients announce the friendly name of the torrent here. | ||
303 | , announcedName :: Maybe ByteString | ||
304 | |||
298 | -- | the port /this/ peer is listening; | 305 | -- | the port /this/ peer is listening; |
299 | , port :: PortNumber | 306 | , port :: PortNumber |
300 | 307 | ||
308 | -- TODO: optional boolean "seed" key | ||
309 | |||
301 | -- | received in response to a previous get_peers query. | 310 | -- | received in response to a previous get_peers query. |
302 | , sessionToken :: Token | 311 | , sessionToken :: Token |
312 | |||
303 | } deriving (Show, Eq, Typeable) | 313 | } deriving (Show, Eq, Typeable) |
304 | 314 | ||
305 | port_key :: BKey | 315 | port_key :: BKey |
@@ -312,6 +322,7 @@ instance BEncode Announce where | |||
312 | toBEncode Announce {..} = toDict $ | 322 | toBEncode Announce {..} = toDict $ |
313 | implied_port_key .=? flagField impliedPort | 323 | implied_port_key .=? flagField impliedPort |
314 | .: info_hash_key .=! topic | 324 | .: info_hash_key .=! topic |
325 | .: name_key .=? announcedName | ||
315 | .: port_key .=! port | 326 | .: port_key .=! port |
316 | .: token_key .=! sessionToken | 327 | .: token_key .=! sessionToken |
317 | .: endDict | 328 | .: endDict |
@@ -321,6 +332,7 @@ instance BEncode Announce where | |||
321 | fromBEncode = fromDict $ do | 332 | fromBEncode = fromDict $ do |
322 | Announce <$> (boolField <$> optional (field (req implied_port_key))) | 333 | Announce <$> (boolField <$> optional (field (req implied_port_key))) |
323 | <*>! info_hash_key | 334 | <*>! info_hash_key |
335 | <*>? name_key | ||
324 | <*>! port_key | 336 | <*>! port_key |
325 | <*>! token_key | 337 | <*>! token_key |
326 | where | 338 | where |
diff --git a/src/Network/BitTorrent/DHT/Query.hs b/src/Network/BitTorrent/DHT/Query.hs index 44083d81..0bec867d 100644 --- a/src/Network/BitTorrent/DHT/Query.hs +++ b/src/Network/BitTorrent/DHT/Query.hs | |||
@@ -105,7 +105,7 @@ findNodeH = nodeHandler $ \ _ (FindNode nid) -> do | |||
105 | NodeFound <$> getClosest nid | 105 | NodeFound <$> getClosest nid |
106 | 106 | ||
107 | -- | Default 'GetPeers' handler. | 107 | -- | Default 'GetPeers' handler. |
108 | getPeersH :: Address ip => NodeHandler ip | 108 | getPeersH :: Ord ip => Address ip => NodeHandler ip |
109 | getPeersH = nodeHandler $ \ naddr (GetPeers ih) -> do | 109 | getPeersH = nodeHandler $ \ naddr (GetPeers ih) -> do |
110 | ps <- getPeerList ih | 110 | ps <- getPeerList ih |
111 | tok <- grantToken naddr | 111 | tok <- grantToken naddr |
@@ -113,19 +113,19 @@ getPeersH = nodeHandler $ \ naddr (GetPeers ih) -> do | |||
113 | return $ GotPeers ps tok | 113 | return $ GotPeers ps tok |
114 | 114 | ||
115 | -- | Default 'Announce' handler. | 115 | -- | Default 'Announce' handler. |
116 | announceH :: Address ip => NodeHandler ip | 116 | announceH :: Ord ip => Address ip => NodeHandler ip |
117 | announceH = nodeHandler $ \ naddr @ NodeAddr {..} (Announce {..}) -> do | 117 | announceH = nodeHandler $ \ naddr @ NodeAddr {..} (Announce {..}) -> do |
118 | valid <- checkToken naddr sessionToken | 118 | valid <- checkToken naddr sessionToken |
119 | unless valid $ do | 119 | unless valid $ do |
120 | throwIO $ InvalidParameter "token" | 120 | throwIO $ InvalidParameter "token" |
121 | 121 | ||
122 | let annPort = if impliedPort then nodePort else port | 122 | let annPort = if impliedPort then nodePort else port |
123 | let peerAddr = PeerAddr Nothing nodeHost annPort | 123 | peerAddr = PeerAddr Nothing nodeHost annPort |
124 | insertPeer topic peerAddr | 124 | insertPeer topic announcedName peerAddr |
125 | return Announced | 125 | return Announced |
126 | 126 | ||
127 | -- | Includes all default query handlers. | 127 | -- | Includes all default query handlers. |
128 | defaultHandlers :: Address ip => [NodeHandler ip] | 128 | defaultHandlers :: Ord ip => Address ip => [NodeHandler ip] |
129 | defaultHandlers = [pingH, findNodeH, getPeersH, announceH] | 129 | defaultHandlers = [pingH, findNodeH, getPeersH, announceH] |
130 | 130 | ||
131 | {----------------------------------------------------------------------- | 131 | {----------------------------------------------------------------------- |
@@ -168,7 +168,7 @@ announceQ ih p NodeInfo {..} = do | |||
168 | | False -> undefined -- TODO check if we can announce | 168 | | False -> undefined -- TODO check if we can announce |
169 | | otherwise -> return (Left ns) | 169 | | otherwise -> return (Left ns) |
170 | Right _ -> do -- TODO *probably* add to peer cache | 170 | Right _ -> do -- TODO *probably* add to peer cache |
171 | Announced <- Announce False ih p grantedToken <@> nodeAddr | 171 | Announced <- Announce False ih Nothing p grantedToken <@> nodeAddr |
172 | return (Right [nodeAddr]) | 172 | return (Right [nodeAddr]) |
173 | 173 | ||
174 | {----------------------------------------------------------------------- | 174 | {----------------------------------------------------------------------- |
diff --git a/src/Network/BitTorrent/DHT/Routing.hs b/src/Network/BitTorrent/DHT/Routing.hs index 38207be5..8a6849a1 100644 --- a/src/Network/BitTorrent/DHT/Routing.hs +++ b/src/Network/BitTorrent/DHT/Routing.hs | |||
@@ -460,7 +460,7 @@ compatibleNodeId tbl = genBucketSample prefix br | |||
460 | where | 460 | where |
461 | br = bucketRange (L.length (shape tbl) - 1) True | 461 | br = bucketRange (L.length (shape tbl) - 1) True |
462 | bs = BS.pack $ take nodeIdSize $ tablePrefix tbl ++ repeat 0 | 462 | bs = BS.pack $ take nodeIdSize $ tablePrefix tbl ++ repeat 0 |
463 | prefix = NodeId bs | 463 | prefix = asNodeId bs |
464 | 464 | ||
465 | tablePrefix :: Table ip -> [Word8] | 465 | tablePrefix :: Table ip -> [Word8] |
466 | tablePrefix = map (packByte . take 8 . (++repeat False)) | 466 | tablePrefix = map (packByte . take 8 . (++repeat False)) |
diff --git a/src/Network/BitTorrent/DHT/Session.hs b/src/Network/BitTorrent/DHT/Session.hs index b85e97fa..339b18eb 100644 --- a/src/Network/BitTorrent/DHT/Session.hs +++ b/src/Network/BitTorrent/DHT/Session.hs | |||
@@ -53,6 +53,7 @@ module Network.BitTorrent.DHT.Session | |||
53 | -- ** Routing table | 53 | -- ** Routing table |
54 | , getTable | 54 | , getTable |
55 | , getClosest | 55 | , getClosest |
56 | , getSwarms | ||
56 | 57 | ||
57 | -- ** Peer storage | 58 | -- ** Peer storage |
58 | , insertPeer | 59 | , insertPeer |
@@ -74,6 +75,7 @@ import Control.Monad.Logger | |||
74 | import Control.Monad.Reader | 75 | import Control.Monad.Reader |
75 | import Control.Monad.Trans.Control | 76 | import Control.Monad.Trans.Control |
76 | import Control.Monad.Trans.Resource | 77 | import Control.Monad.Trans.Resource |
78 | import Data.ByteString | ||
77 | import Data.Conduit.Lazy | 79 | import Data.Conduit.Lazy |
78 | import Data.Default | 80 | import Data.Default |
79 | import Data.Fixed | 81 | import Data.Fixed |
@@ -89,7 +91,8 @@ import Data.Torrent as Torrent | |||
89 | import Network.KRPC as KRPC hiding (Options, def) | 91 | import Network.KRPC as KRPC hiding (Options, def) |
90 | import qualified Network.KRPC as KRPC (def) | 92 | import qualified Network.KRPC as KRPC (def) |
91 | import Network.BitTorrent.Address | 93 | import Network.BitTorrent.Address |
92 | import Network.BitTorrent.DHT.ContactInfo as P | 94 | import Network.BitTorrent.DHT.ContactInfo (PeerStore) |
95 | import qualified Network.BitTorrent.DHT.ContactInfo as P | ||
93 | import Network.BitTorrent.DHT.Message | 96 | import Network.BitTorrent.DHT.Message |
94 | import Network.BitTorrent.DHT.Routing as R | 97 | import Network.BitTorrent.DHT.Routing as R |
95 | import Network.BitTorrent.DHT.Token as T | 98 | import Network.BitTorrent.DHT.Token as T |
@@ -395,6 +398,11 @@ getTable = do | |||
395 | let nil = nullTable myId (optBucketCount opts) | 398 | let nil = nullTable myId (optBucketCount opts) |
396 | liftIO (maybe nil R.myBuckets <$> atomically (readTVar var)) | 399 | liftIO (maybe nil R.myBuckets <$> atomically (readTVar var)) |
397 | 400 | ||
401 | getSwarms :: Ord ip => DHT ip [ (InfoHash, Int, Maybe ByteString) ] | ||
402 | getSwarms = do | ||
403 | store <- asks contactInfo >>= liftIO . atomically . readTVar | ||
404 | return $ P.knownSwarms store | ||
405 | |||
398 | -- | Find a set of closest nodes from routing table of this node. (in | 406 | -- | Find a set of closest nodes from routing table of this node. (in |
399 | -- no particular order) | 407 | -- no particular order) |
400 | -- | 408 | -- |
@@ -416,14 +424,14 @@ refreshContacts = | |||
416 | 424 | ||
417 | 425 | ||
418 | -- | Insert peer to peer store. Used to handle announce requests. | 426 | -- | Insert peer to peer store. Used to handle announce requests. |
419 | insertPeer :: Eq ip => InfoHash -> PeerAddr ip -> DHT ip () | 427 | insertPeer :: Ord ip => InfoHash -> Maybe ByteString -> PeerAddr ip -> DHT ip () |
420 | insertPeer ih addr = do | 428 | insertPeer ih name addr = do |
421 | refreshContacts | 429 | refreshContacts |
422 | var <- asks contactInfo | 430 | var <- asks contactInfo |
423 | liftIO $ atomically $ modifyTVar' var (P.insert ih addr) | 431 | liftIO $ atomically $ modifyTVar' var (P.insertPeer ih name addr) |
424 | 432 | ||
425 | -- | Get peer set for specific swarm. | 433 | -- | Get peer set for specific swarm. |
426 | lookupPeers :: InfoHash -> DHT ip [PeerAddr ip] | 434 | lookupPeers :: Ord ip => InfoHash -> DHT ip [PeerAddr ip] |
427 | lookupPeers ih = do | 435 | lookupPeers ih = do |
428 | refreshContacts | 436 | refreshContacts |
429 | var <- asks contactInfo | 437 | var <- asks contactInfo |
@@ -433,7 +441,7 @@ lookupPeers ih = do | |||
433 | -- | 441 | -- |
434 | -- This operation use 'getClosest' as failback so it may block. | 442 | -- This operation use 'getClosest' as failback so it may block. |
435 | -- | 443 | -- |
436 | getPeerList :: Eq ip => InfoHash -> DHT ip (PeerList ip) | 444 | getPeerList :: Ord ip => InfoHash -> DHT ip (PeerList ip) |
437 | getPeerList ih = do | 445 | getPeerList ih = do |
438 | ps <- lookupPeers ih | 446 | ps <- lookupPeers ih |
439 | if L.null ps | 447 | if L.null ps |