diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Data/Torrent.hs | 13 | ||||
-rw-r--r-- | src/Network/BitTorrent/Address.hs | 12 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT.hs | 3 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/ContactInfo.hs | 1 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Message.hs | 4 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Query.hs | 34 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Routing.hs | 53 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Session.hs | 15 | ||||
-rw-r--r-- | src/Network/BitTorrent/DHT/Token.hs | 3 |
9 files changed, 45 insertions, 93 deletions
diff --git a/src/Data/Torrent.hs b/src/Data/Torrent.hs index 6bec665e..c22ca189 100644 --- a/src/Data/Torrent.hs +++ b/src/Data/Torrent.hs | |||
@@ -19,7 +19,6 @@ | |||
19 | {-# LANGUAGE CPP #-} | 19 | {-# LANGUAGE CPP #-} |
20 | {-# LANGUAGE NamedFieldPuns #-} | 20 | {-# LANGUAGE NamedFieldPuns #-} |
21 | {-# LANGUAGE FlexibleInstances #-} | 21 | {-# LANGUAGE FlexibleInstances #-} |
22 | {-# LANGUAGE OverlappingInstances #-} | ||
23 | {-# LANGUAGE MultiParamTypeClasses #-} | 22 | {-# LANGUAGE MultiParamTypeClasses #-} |
24 | {-# LANGUAGE BangPatterns #-} | 23 | {-# LANGUAGE BangPatterns #-} |
25 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 24 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
@@ -166,7 +165,6 @@ import Data.ByteString.Lazy as BL | |||
166 | import Data.Char | 165 | import Data.Char |
167 | import Data.Convertible | 166 | import Data.Convertible |
168 | import Data.Default | 167 | import Data.Default |
169 | import Data.Foldable as F | ||
170 | import Data.Hashable as Hashable | 168 | import Data.Hashable as Hashable |
171 | import Data.Int | 169 | import Data.Int |
172 | import Data.List as L | 170 | import Data.List as L |
@@ -666,15 +664,6 @@ instance NFData PieceInfo where | |||
666 | instance Default PieceInfo where | 664 | instance Default PieceInfo where |
667 | def = PieceInfo 1 def | 665 | def = PieceInfo 1 def |
668 | 666 | ||
669 | class Lint a where | ||
670 | lint :: a -> Either String a | ||
671 | |||
672 | instance Lint PieceInfo where | ||
673 | lint pinfo @ PieceInfo {..} | ||
674 | | BS.length (unHashList piPieceHashes) `rem` hashsize == 0 | ||
675 | , piPieceLength >= 0 = return pinfo | ||
676 | | otherwise = Left undefined | ||
677 | |||
678 | 667 | ||
679 | putPieceInfo :: Data.Torrent.Put PieceInfo | 668 | putPieceInfo :: Data.Torrent.Put PieceInfo |
680 | putPieceInfo PieceInfo {..} cont = | 669 | putPieceInfo PieceInfo {..} cont = |
@@ -898,7 +887,7 @@ instance BEncode POSIXTime where | |||
898 | fromBEncode _ = decodingError $ "POSIXTime" | 887 | fromBEncode _ = decodingError $ "POSIXTime" |
899 | 888 | ||
900 | -- TODO to bencoding package | 889 | -- TODO to bencoding package |
901 | instance BEncode String where | 890 | instance {-# OVERLAPPING #-} BEncode String where |
902 | toBEncode = toBEncode . T.pack | 891 | toBEncode = toBEncode . T.pack |
903 | fromBEncode v = T.unpack <$> fromBEncode v | 892 | fromBEncode v = T.unpack <$> fromBEncode v |
904 | 893 | ||
diff --git a/src/Network/BitTorrent/Address.hs b/src/Network/BitTorrent/Address.hs index fea7139d..f8f29be5 100644 --- a/src/Network/BitTorrent/Address.hs +++ b/src/Network/BitTorrent/Address.hs | |||
@@ -99,7 +99,6 @@ import qualified Data.ByteString.Lazy.Builder as BS | |||
99 | import Data.Char | 99 | import Data.Char |
100 | import Data.Convertible | 100 | import Data.Convertible |
101 | import Data.Default | 101 | import Data.Default |
102 | import Data.Foldable | ||
103 | import Data.IP | 102 | import Data.IP |
104 | import Data.List as L | 103 | import Data.List as L |
105 | import Data.List.Split as L | 104 | import Data.List.Split as L |
@@ -165,13 +164,13 @@ instance Address IP where | |||
165 | setPort :: PortNumber -> SockAddr -> SockAddr | 164 | setPort :: PortNumber -> SockAddr -> SockAddr |
166 | setPort port (SockAddrInet _ h ) = SockAddrInet port h | 165 | setPort port (SockAddrInet _ h ) = SockAddrInet port h |
167 | setPort port (SockAddrInet6 _ f h s) = SockAddrInet6 port f h s | 166 | setPort port (SockAddrInet6 _ f h s) = SockAddrInet6 port f h s |
168 | setPort _ (SockAddrUnix s ) = SockAddrUnix s | 167 | setPort _ addr = addr |
169 | {-# INLINE setPort #-} | 168 | {-# INLINE setPort #-} |
170 | 169 | ||
171 | getPort :: SockAddr -> Maybe PortNumber | 170 | getPort :: SockAddr -> Maybe PortNumber |
172 | getPort (SockAddrInet p _ ) = Just p | 171 | getPort (SockAddrInet p _ ) = Just p |
173 | getPort (SockAddrInet6 p _ _ _) = Just p | 172 | getPort (SockAddrInet6 p _ _ _) = Just p |
174 | getPort (SockAddrUnix _ ) = Nothing | 173 | getPort _ = Nothing |
175 | {-# INLINE getPort #-} | 174 | {-# INLINE getPort #-} |
176 | 175 | ||
177 | instance Address a => Address (NodeAddr a) where | 176 | instance Address a => Address (NodeAddr a) where |
@@ -689,7 +688,7 @@ newtype NodeDistance = NodeDistance BS.ByteString | |||
689 | instance Pretty NodeDistance where | 688 | instance Pretty NodeDistance where |
690 | pPrint (NodeDistance bs) = foldMap bitseq $ BS.unpack bs | 689 | pPrint (NodeDistance bs) = foldMap bitseq $ BS.unpack bs |
691 | where | 690 | where |
692 | listBits w = L.map (testBit w) (L.reverse [0..bitSize w - 1]) | 691 | listBits w = L.map (testBit w) (L.reverse [0..finiteBitSize w - 1]) |
693 | bitseq = foldMap (int . fromEnum) . listBits | 692 | bitseq = foldMap (int . fromEnum) . listBits |
694 | 693 | ||
695 | -- | distance(A,B) = |A xor B| Smaller values are closer. | 694 | -- | distance(A,B) = |A xor B| Smaller values are closer. |
@@ -1232,6 +1231,7 @@ bep42s addr (NodeId r) = mapMaybe (bep42 addr) rs | |||
1232 | where | 1231 | where |
1233 | rs = L.map (NodeId . change3bits r) [0..7] | 1232 | rs = L.map (NodeId . change3bits r) [0..7] |
1234 | 1233 | ||
1234 | change3bits :: ByteString -> Word8 -> ByteString | ||
1235 | change3bits bs n = BS.snoc (BS.init bs) (BS.last bs .&. 0xF8 .|. n) | 1235 | change3bits bs n = BS.snoc (BS.init bs) (BS.last bs .&. 0xF8 .|. n) |
1236 | 1236 | ||
1237 | -- | Modifies a purely random 'NodeId' to one that is related to a given | 1237 | -- | Modifies a purely random 'NodeId' to one that is related to a given |
@@ -1240,7 +1240,7 @@ bep42 :: Address a => a -> NodeId -> Maybe NodeId | |||
1240 | bep42 addr (NodeId r) | 1240 | bep42 addr (NodeId r) |
1241 | | Just ip <- fmap S.encode (fromAddr addr :: Maybe IPv4) | 1241 | | Just ip <- fmap S.encode (fromAddr addr :: Maybe IPv4) |
1242 | <|> fmap S.encode (fromAddr addr :: Maybe IPv6) | 1242 | <|> fmap S.encode (fromAddr addr :: Maybe IPv6) |
1243 | = genBucketSample' retr (NodeId $ crc $ masked ip) (3,0x07,0) | 1243 | = genBucketSample' retr (NodeId $ crc $ applyMask ip) (3,0x07,0) |
1244 | | otherwise | 1244 | | otherwise |
1245 | = Nothing | 1245 | = Nothing |
1246 | where | 1246 | where |
@@ -1249,7 +1249,7 @@ bep42 addr (NodeId r) | |||
1249 | nbhood_select = BS.last r .&. 7 | 1249 | nbhood_select = BS.last r .&. 7 |
1250 | retr n = pure $ BS.drop (BS.length r - n) r | 1250 | retr n = pure $ BS.drop (BS.length r - n) r |
1251 | crc = S.encode . crc32c . BS.pack | 1251 | crc = S.encode . crc32c . BS.pack |
1252 | masked ip = case BS.zipWith (.&.) msk ip of | 1252 | applyMask ip = case BS.zipWith (.&.) msk ip of |
1253 | (b:bs) -> (b .|. shiftL nbhood_select 5) : bs | 1253 | (b:bs) -> (b .|. shiftL nbhood_select 5) : bs |
1254 | bs -> bs | 1254 | bs -> bs |
1255 | where msk | BS.length ip == 4 = ip4mask | 1255 | where msk | BS.length ip == 4 = ip4mask |
diff --git a/src/Network/BitTorrent/DHT.hs b/src/Network/BitTorrent/DHT.hs index 7ca8fc8b..45c87831 100644 --- a/src/Network/BitTorrent/DHT.hs +++ b/src/Network/BitTorrent/DHT.hs | |||
@@ -53,7 +53,6 @@ module Network.BitTorrent.DHT | |||
53 | , runDHT | 53 | , runDHT |
54 | ) where | 54 | ) where |
55 | 55 | ||
56 | import Control.Applicative | ||
57 | import Control.Monad.Logger | 56 | import Control.Monad.Logger |
58 | import Control.Monad.Reader | 57 | import Control.Monad.Reader |
59 | import Control.Exception | 58 | import Control.Exception |
@@ -281,6 +280,6 @@ insert ih p = do | |||
281 | -- | 280 | -- |
282 | -- This operation is atomic and may block for a while. | 281 | -- This operation is atomic and may block for a while. |
283 | -- | 282 | -- |
284 | delete :: Address ip => InfoHash -> PortNumber -> DHT ip () | 283 | delete :: InfoHash -> PortNumber -> DHT ip () |
285 | delete = deleteTopic | 284 | delete = deleteTopic |
286 | {-# INLINE delete #-} | 285 | {-# INLINE delete #-} |
diff --git a/src/Network/BitTorrent/DHT/ContactInfo.hs b/src/Network/BitTorrent/DHT/ContactInfo.hs index baa240b4..4293506d 100644 --- a/src/Network/BitTorrent/DHT/ContactInfo.hs +++ b/src/Network/BitTorrent/DHT/ContactInfo.hs | |||
@@ -7,7 +7,6 @@ module Network.BitTorrent.DHT.ContactInfo | |||
7 | import Data.Default | 7 | import Data.Default |
8 | import Data.List as L | 8 | import Data.List as L |
9 | import Data.Maybe | 9 | import Data.Maybe |
10 | import Data.Monoid | ||
11 | import Data.HashMap.Strict as HM | 10 | import Data.HashMap.Strict as HM |
12 | import Data.Serialize | 11 | import Data.Serialize |
13 | 12 | ||
diff --git a/src/Network/BitTorrent/DHT/Message.hs b/src/Network/BitTorrent/DHT/Message.hs index b8f272c3..9d66741f 100644 --- a/src/Network/BitTorrent/DHT/Message.hs +++ b/src/Network/BitTorrent/DHT/Message.hs | |||
@@ -94,7 +94,7 @@ import Network | |||
94 | import Network.KRPC | 94 | import Network.KRPC |
95 | import Data.Maybe | 95 | import Data.Maybe |
96 | 96 | ||
97 | import Data.Torrent | 97 | import Data.Torrent (InfoHash) |
98 | import Network.BitTorrent.Address | 98 | import Network.BitTorrent.Address |
99 | import Network.BitTorrent.DHT.Token | 99 | import Network.BitTorrent.DHT.Token |
100 | import Network.KRPC () | 100 | import Network.KRPC () |
@@ -204,7 +204,7 @@ binary k = field (req k) >>= either (fail . format) return . | |||
204 | where | 204 | where |
205 | format str = "fail to deserialize " ++ show k ++ " field: " ++ str | 205 | format str = "fail to deserialize " ++ show k ++ " field: " ++ str |
206 | 206 | ||
207 | instance (Typeable ip, Address ip) => BEncode (NodeFound ip) where | 207 | instance Address ip => BEncode (NodeFound ip) where |
208 | toBEncode (NodeFound ns) = toDict $ | 208 | toBEncode (NodeFound ns) = toDict $ |
209 | nodes_key .=! runPut (mapM_ put ns) | 209 | nodes_key .=! runPut (mapM_ put ns) |
210 | .: endDict | 210 | .: endDict |
diff --git a/src/Network/BitTorrent/DHT/Query.hs b/src/Network/BitTorrent/DHT/Query.hs index d1fa36e5..e067ab52 100644 --- a/src/Network/BitTorrent/DHT/Query.hs +++ b/src/Network/BitTorrent/DHT/Query.hs | |||
@@ -49,7 +49,6 @@ module Network.BitTorrent.DHT.Query | |||
49 | , (<@>) | 49 | , (<@>) |
50 | ) where | 50 | ) where |
51 | 51 | ||
52 | import Control.Applicative | ||
53 | import Control.Concurrent.Lifted hiding (yield) | 52 | import Control.Concurrent.Lifted hiding (yield) |
54 | import Control.Exception.Lifted hiding (Handler) | 53 | import Control.Exception.Lifted hiding (Handler) |
55 | import Control.Monad.Reader | 54 | import Control.Monad.Reader |
@@ -168,7 +167,7 @@ announceQ ih p NodeInfo {..} = do | |||
168 | Left ns | 167 | Left ns |
169 | | False -> undefined -- TODO check if we can announce | 168 | | False -> undefined -- TODO check if we can announce |
170 | | otherwise -> return (Left ns) | 169 | | otherwise -> return (Left ns) |
171 | Right ps -> do -- TODO *probably* add to peer cache | 170 | Right _ -> do -- TODO *probably* add to peer cache |
172 | Announced <- Announce False ih p grantedToken <@> nodeAddr | 171 | Announced <- Announce False ih p grantedToken <@> nodeAddr |
173 | return (Right [nodeAddr]) | 172 | return (Right [nodeAddr]) |
174 | 173 | ||
@@ -179,7 +178,7 @@ announceQ ih p NodeInfo {..} = do | |||
179 | type Search ip o = Conduit [NodeInfo ip] (DHT ip) [o ip] | 178 | type Search ip o = Conduit [NodeInfo ip] (DHT ip) [o ip] |
180 | 179 | ||
181 | -- TODO: use reorder and filter (Traversal option) leftovers | 180 | -- TODO: use reorder and filter (Traversal option) leftovers |
182 | search :: TableKey k => Address ip => k -> Iteration ip o -> Search ip o | 181 | search :: k -> Iteration ip o -> Search ip o |
183 | search _ action = do | 182 | search _ action = do |
184 | awaitForever $ \ batch -> unless (L.null batch) $ do | 183 | awaitForever $ \ batch -> unless (L.null batch) $ do |
185 | $(logWarnS) "search" "start query" | 184 | $(logWarnS) "search" "start query" |
@@ -196,11 +195,6 @@ publish ih p = do | |||
196 | _ <- sourceList [nodes] $= search ih (announceQ ih p) $$ C.take r | 195 | _ <- sourceList [nodes] $= search ih (announceQ ih p) $$ C.take r |
197 | return () | 196 | return () |
198 | 197 | ||
199 | republish :: DHT ip ThreadId | ||
200 | republish = fork $ do | ||
201 | i <- asks (optReannounce . options) | ||
202 | error "DHT.republish: not implemented" | ||
203 | |||
204 | getTimestamp :: DHT ip Timestamp | 198 | getTimestamp :: DHT ip Timestamp |
205 | getTimestamp = do | 199 | getTimestamp = do |
206 | utcTime <- liftIO $ getCurrentTime | 200 | utcTime <- liftIO $ getCurrentTime |
@@ -229,7 +223,7 @@ refreshNodes nid = do | |||
229 | -- nss <- sourceList [[addr]] $= search nid (findNodeQ nid) $$ C.consume | 223 | -- nss <- sourceList [[addr]] $= search nid (findNodeQ nid) $$ C.consume |
230 | nss <- sourceList [nodes] $= search nid (findNodeQ nid) $$ C.consume | 224 | nss <- sourceList [nodes] $= search nid (findNodeQ nid) $$ C.consume |
231 | $(logWarnS) "refreshNodes" $ "received " <> T.pack (show (L.length (L.concat nss))) <> " nodes." | 225 | $(logWarnS) "refreshNodes" $ "received " <> T.pack (show (L.length (L.concat nss))) <> " nodes." |
232 | queryParallel $ flip L.map (L.concat nss) $ \n -> do | 226 | _ <- queryParallel $ flip L.map (L.concat nss) $ \n -> do |
233 | $(logWarnS) "refreshNodes" $ "received node: " <> T.pack (show (pPrint n)) | 227 | $(logWarnS) "refreshNodes" $ "received node: " <> T.pack (show (pPrint n)) |
234 | pingQ (nodeAddr n) | 228 | pingQ (nodeAddr n) |
235 | -- pingQ takes care of inserting the node. | 229 | -- pingQ takes care of inserting the node. |
@@ -239,15 +233,14 @@ refreshNodes nid = do | |||
239 | -- | This operation do not block but acquire exclusive access to | 233 | -- | This operation do not block but acquire exclusive access to |
240 | -- routing table. | 234 | -- routing table. |
241 | insertNode :: Address ip => NodeInfo ip -> Maybe ReflectedIP -> DHT ip ThreadId | 235 | insertNode :: Address ip => NodeInfo ip -> Maybe ReflectedIP -> DHT ip ThreadId |
242 | insertNode info witnessed_ip = fork $ do | 236 | insertNode info witnessed_ip0 = fork $ do |
243 | var <- asks routingInfo | 237 | var <- asks routingInfo |
244 | tm <- getTimestamp | 238 | tm <- getTimestamp |
245 | let showTable = do | 239 | let showTable = do |
246 | t <- getTable | 240 | t <- getTable |
247 | let logMsg = "Routing table: " <> pPrint t | 241 | let logMsg = "Routing table: " <> pPrint t |
248 | $(logDebugS) "insertNode" (T.pack (render logMsg)) | 242 | $(logDebugS) "insertNode" (T.pack (render logMsg)) |
249 | t <- liftIO $ atomically $ readTVar var | 243 | let arrival0 = TryInsert info |
250 | let arrival = TryInsert info | ||
251 | arrival4 = TryInsert (fmap fromAddr info) :: Event (Maybe IPv4) | 244 | arrival4 = TryInsert (fmap fromAddr info) :: Event (Maybe IPv4) |
252 | $(logDebugS) "insertNode" $ T.pack (show arrival4) | 245 | $(logDebugS) "insertNode" $ T.pack (show arrival4) |
253 | maxbuckets <- asks (optBucketCount . options) | 246 | maxbuckets <- asks (optBucketCount . options) |
@@ -259,13 +252,13 @@ insertNode info witnessed_ip = fork $ do | |||
259 | $ rank id (nodeId $ foreignNode arrival) | 252 | $ rank id (nodeId $ foreignNode arrival) |
260 | $ bep42s ip fallbackid | 253 | $ bep42s ip fallbackid |
261 | case minfo of | 254 | case minfo of |
262 | Just info -> do | 255 | Just inf -> do |
263 | (ps,t') <- R.insert tm arrival $ myBuckets info | 256 | (ps,t') <- R.insert tm arrival $ myBuckets inf |
264 | writeTVar var $ Just $ info { myBuckets = t' } | 257 | writeTVar var $ Just $ inf { myBuckets = t' } |
265 | return $ do | 258 | return $ do |
266 | case witnessed_ip of | 259 | case witnessed_ip of |
267 | Just (ReflectedIP ip0) | 260 | Just (ReflectedIP ip0) |
268 | | fromSockAddr ip0 /= Just (myAddress info) | 261 | | fromSockAddr ip0 /= Just (myAddress inf) |
269 | -> $(logInfo) ( T.pack $ L.unwords | 262 | -> $(logInfo) ( T.pack $ L.unwords |
270 | $ [ "Possible NAT?" | 263 | $ [ "Possible NAT?" |
271 | , show (toSockAddr $ nodeAddr $ foreignNode arrival) | 264 | , show (toSockAddr $ nodeAddr $ foreignNode arrival) |
@@ -298,15 +291,14 @@ insertNode info witnessed_ip = fork $ do | |||
298 | <> ")" | 291 | <> ")" |
299 | ] ) | 292 | ] ) |
300 | return ps | 293 | return ps |
301 | ps <- join $ liftIO $ atomically $ atomicInsert arrival witnessed_ip | 294 | ps <- join $ liftIO $ atomically $ atomicInsert arrival0 witnessed_ip0 |
302 | showTable | 295 | showTable |
303 | fork $ forM_ ps $ \(CheckPing ns)-> do | 296 | _ <- fork $ forM_ ps $ \(CheckPing ns)-> do |
304 | forM_ ns $ \n -> do | 297 | forM_ ns $ \n -> do |
305 | (b,mip) <- probeNode (nodeAddr n) | 298 | (b,mip) <- probeNode (nodeAddr n) |
306 | let alive = PingResult n b | 299 | let alive = PingResult n b |
307 | $(logDebugS) "insertNode" $ T.pack ("PingResult "++show (nodeId n,b)) | 300 | $(logDebugS) "insertNode" $ T.pack ("PingResult "++show (nodeId n,b)) |
308 | tm <- getTimestamp | 301 | _ <- join $ liftIO $ atomically $ atomicInsert alive mip |
309 | join $ liftIO $ atomically $ atomicInsert alive mip | ||
310 | showTable | 302 | showTable |
311 | return () | 303 | return () |
312 | 304 | ||
@@ -323,7 +315,7 @@ queryNode' addr q = do | |||
323 | (Response remoteId r, witnessed_ip) <- query' (toSockAddr addr) (Query nid read_only q) | 315 | (Response remoteId r, witnessed_ip) <- query' (toSockAddr addr) (Query nid read_only q) |
324 | -- $(logDebugS) "queryNode" $ "Witnessed address: " <> T.pack (show witnessed_ip) | 316 | -- $(logDebugS) "queryNode" $ "Witnessed address: " <> T.pack (show witnessed_ip) |
325 | -- <> " by " <> T.pack (show (toSockAddr addr)) | 317 | -- <> " by " <> T.pack (show (toSockAddr addr)) |
326 | insertNode (NodeInfo remoteId addr) witnessed_ip | 318 | _ <- insertNode (NodeInfo remoteId addr) witnessed_ip |
327 | return (remoteId, r, witnessed_ip) | 319 | return (remoteId, r, witnessed_ip) |
328 | 320 | ||
329 | -- | Infix version of 'queryNode' function. | 321 | -- | Infix version of 'queryNode' function. |
diff --git a/src/Network/BitTorrent/DHT/Routing.hs b/src/Network/BitTorrent/DHT/Routing.hs index 84e4d4ce..f9d64eea 100644 --- a/src/Network/BitTorrent/DHT/Routing.hs +++ b/src/Network/BitTorrent/DHT/Routing.hs | |||
@@ -144,7 +144,7 @@ instance Alternative (Routing ip) where | |||
144 | Refresh n f <|> m = Refresh n (f <|> m) | 144 | Refresh n f <|> m = Refresh n (f <|> m) |
145 | 145 | ||
146 | -- | Run routing table operation. | 146 | -- | Run routing table operation. |
147 | runRouting :: (Monad m, Eq ip) | 147 | runRouting :: Monad m |
148 | => (NodeAddr ip -> m Bool) -- ^ ping the specific node; | 148 | => (NodeAddr ip -> m Bool) -- ^ ping the specific node; |
149 | -> (NodeId -> m ()) -- ^ refresh nodes; | 149 | -> (NodeId -> m ()) -- ^ refresh nodes; |
150 | -> m Timestamp -- ^ get current time; | 150 | -> m Timestamp -- ^ get current time; |
@@ -166,18 +166,6 @@ runRouting ping_node find_nodes timestamper = go | |||
166 | find_nodes nid | 166 | find_nodes nid |
167 | go f | 167 | go f |
168 | 168 | ||
169 | getTime :: Routing ip Timestamp | ||
170 | getTime = GetTime return | ||
171 | {-# INLINE getTime #-} | ||
172 | |||
173 | needPing :: NodeAddr ip -> Routing ip Bool | ||
174 | needPing addr = NeedPing addr return | ||
175 | {-# INLINE needPing #-} | ||
176 | |||
177 | refresh :: NodeId -> Routing ip () | ||
178 | refresh nid = Refresh nid (Done ()) | ||
179 | {-# INLINE refresh #-} | ||
180 | |||
181 | {----------------------------------------------------------------------- | 169 | {----------------------------------------------------------------------- |
182 | Bucket | 170 | Bucket |
183 | -----------------------------------------------------------------------} | 171 | -----------------------------------------------------------------------} |
@@ -213,6 +201,7 @@ data QueueMethods m elem fifo = QueueMethods | |||
213 | , emptyQueue :: m fifo | 201 | , emptyQueue :: m fifo |
214 | } | 202 | } |
215 | 203 | ||
204 | {- | ||
216 | fromQ :: Functor m => | 205 | fromQ :: Functor m => |
217 | ( a -> b ) | 206 | ( a -> b ) |
218 | -> ( b -> a ) | 207 | -> ( b -> a ) |
@@ -223,6 +212,7 @@ fromQ embed project QueueMethods{..} = | |||
223 | , popFront = fmap (second embed) . popFront . project | 212 | , popFront = fmap (second embed) . popFront . project |
224 | , emptyQueue = fmap embed emptyQueue | 213 | , emptyQueue = fmap embed emptyQueue |
225 | } | 214 | } |
215 | -} | ||
226 | 216 | ||
227 | seqQ :: QueueMethods Identity (NodeInfo ip) (Seq.Seq (NodeInfo ip)) | 217 | seqQ :: QueueMethods Identity (NodeInfo ip) (Seq.Seq (NodeInfo ip)) |
228 | seqQ = QueueMethods | 218 | seqQ = QueueMethods |
@@ -256,17 +246,6 @@ instance (Serialize k, Serialize v, Ord k, Ord v) | |||
256 | get = PSQ.fromList <$> get | 246 | get = PSQ.fromList <$> get |
257 | put = put . PSQ.toList | 247 | put = put . PSQ.toList |
258 | 248 | ||
259 | -- | Get the most recently changed node entry, if any. | ||
260 | lastChanged :: Eq ip => Bucket ip -> Maybe (NodeEntry ip) | ||
261 | lastChanged bucket | ||
262 | | L.null timestamps = Nothing | ||
263 | | otherwise = Just (L.maximumBy (compare `on` prio) timestamps) | ||
264 | where | ||
265 | timestamps = PSQ.toList $ bktNodes bucket | ||
266 | |||
267 | leastRecently :: Eq ip => Bucket ip -> Maybe (NodeEntry ip, Bucket ip) | ||
268 | leastRecently b = fmap (\(e,ns) -> (e, b { bktNodes = ns })) $ minView $ bktNodes b | ||
269 | |||
270 | -- | Update interval, in seconds. | 249 | -- | Update interval, in seconds. |
271 | delta :: NominalDiffTime | 250 | delta :: NominalDiffTime |
272 | delta = 15 * 60 | 251 | delta = 15 * 60 |
@@ -303,29 +282,30 @@ insertBucket curTime (TryInsert info) bucket | |||
303 | map_q f = bucket { bktQ = runIdentity $ f (bktQ bucket) } | 282 | map_q f = bucket { bktQ = runIdentity $ f (bktQ bucket) } |
304 | 283 | ||
305 | insertBucket curTime (PingResult bad_node got_response) bucket | 284 | insertBucket curTime (PingResult bad_node got_response) bucket |
306 | = pure ([], Bucket (update $ bktNodes bucket) popped) | 285 | = pure ([], Bucket (upd $ bktNodes bucket) popped) |
307 | where | 286 | where |
308 | (top, popped) = runIdentity $ popFront bucketQ (bktQ bucket) | 287 | (top, popped) = runIdentity $ popFront bucketQ (bktQ bucket) |
309 | update | got_response = id | 288 | upd | got_response = id |
310 | | Just info <- top = PSQ.insert info curTime . PSQ.delete bad_node | 289 | | Just info <- top = PSQ.insert info curTime . PSQ.delete bad_node |
311 | | otherwise = id | 290 | | otherwise = id |
312 | 291 | ||
313 | type BitIx = Word | 292 | type BitIx = Word |
314 | 293 | ||
315 | partitionQ imp pred q = do | 294 | partitionQ :: Monad f => QueueMethods f elem b -> (elem -> Bool) -> b -> f (b, b) |
316 | pass <- emptyQueue imp | 295 | partitionQ imp test q0 = do |
317 | fail <- emptyQueue imp | 296 | pass0 <- emptyQueue imp |
297 | fail0 <- emptyQueue imp | ||
318 | let flipfix a b f = fix f a b | 298 | let flipfix a b f = fix f a b |
319 | flipfix q (pass,fail) $ \loop q qs -> do | 299 | flipfix q0 (pass0,fail0) $ \rec q qs -> do |
320 | (mb,q') <- popFront imp q | 300 | (mb,q') <- popFront imp q |
321 | case mb of | 301 | case mb of |
322 | Nothing -> return qs | 302 | Nothing -> return qs |
323 | Just e -> do qs' <- select (pushBack imp e) qs | 303 | Just e -> do qs' <- select (pushBack imp e) qs |
324 | loop q' qs' | 304 | rec q' qs' |
325 | where | 305 | where |
326 | select :: Functor f => (b -> f b) -> (b, b) -> f (b, b) | 306 | select :: Functor f => (b -> f b) -> (b, b) -> f (b, b) |
327 | select f = if pred e then \(a,b) -> flip (,) b <$> f a | 307 | select f = if test e then \(a,b) -> flip (,) b <$> f a |
328 | else \(a,b) -> (,) a <$> f b | 308 | else \(a,b) -> (,) a <$> f b |
329 | 309 | ||
330 | split :: Eq ip => BitIx -> Bucket ip -> (Bucket ip, Bucket ip) | 310 | split :: Eq ip => BitIx -> Bucket ip -> (Bucket ip, Bucket ip) |
331 | split i b = (Bucket ns qs, Bucket ms rs) | 311 | split i b = (Bucket ns qs, Bucket ms rs) |
@@ -529,7 +509,7 @@ splitTip nid n i bucket | |||
529 | -- k nodes in them. Which subtrees I mean is illustrated in Fig 1. of Kademlia | 509 | -- k nodes in them. Which subtrees I mean is illustrated in Fig 1. of Kademlia |
530 | -- paper. The rule requiring additional splits is in section 2.4. | 510 | -- paper. The rule requiring additional splits is in section 2.4. |
531 | modifyBucket | 511 | modifyBucket |
532 | :: forall f ip xs. (Alternative f, Eq ip, Monoid xs) => | 512 | :: forall f ip xs. (Alternative f, Eq ip) => |
533 | NodeId -> (Bucket ip -> f (xs, Bucket ip)) -> Table ip -> f (xs,Table ip) | 513 | NodeId -> (Bucket ip -> f (xs, Bucket ip)) -> Table ip -> f (xs,Table ip) |
534 | modifyBucket nodeId f = go (0 :: BitIx) | 514 | modifyBucket nodeId f = go (0 :: BitIx) |
535 | where | 515 | where |
@@ -552,6 +532,7 @@ data Event ip = TryInsert { foreignNode :: NodeInfo ip } | |||
552 | } | 532 | } |
553 | deriving (Eq,Ord,Show) | 533 | deriving (Eq,Ord,Show) |
554 | 534 | ||
535 | eventId :: Event ip -> NodeId | ||
555 | eventId (TryInsert NodeInfo{..}) = nodeId | 536 | eventId (TryInsert NodeInfo{..}) = nodeId |
556 | eventId (PingResult NodeInfo{..} _) = nodeId | 537 | eventId (PingResult NodeInfo{..} _) = nodeId |
557 | 538 | ||
diff --git a/src/Network/BitTorrent/DHT/Session.hs b/src/Network/BitTorrent/DHT/Session.hs index 44a5f0e9..d9a50a15 100644 --- a/src/Network/BitTorrent/DHT/Session.hs +++ b/src/Network/BitTorrent/DHT/Session.hs | |||
@@ -66,9 +66,7 @@ module Network.BitTorrent.DHT.Session | |||
66 | 66 | ||
67 | import Prelude hiding (ioError) | 67 | import Prelude hiding (ioError) |
68 | 68 | ||
69 | import Control.Applicative | ||
70 | import Control.Concurrent.STM | 69 | import Control.Concurrent.STM |
71 | import Control.Concurrent.Lifted hiding (yield) | ||
72 | import Control.Concurrent.Async.Lifted | 70 | import Control.Concurrent.Async.Lifted |
73 | import Control.Exception.Lifted hiding (Handler) | 71 | import Control.Exception.Lifted hiding (Handler) |
74 | import Control.Monad.Base | 72 | import Control.Monad.Base |
@@ -82,16 +80,10 @@ import Data.Fixed | |||
82 | import Data.Hashable | 80 | import Data.Hashable |
83 | import Data.List as L | 81 | import Data.List as L |
84 | import Data.Maybe | 82 | import Data.Maybe |
85 | import Data.Monoid | ||
86 | import Data.Set as S | 83 | import Data.Set as S |
87 | import Data.Text as T | ||
88 | import Data.Time | 84 | import Data.Time |
89 | import Data.Time.Clock.POSIX | ||
90 | import Network (PortNumber) | 85 | import Network (PortNumber) |
91 | import System.Log.FastLogger | ||
92 | import System.Random (randomIO) | 86 | import System.Random (randomIO) |
93 | import Text.PrettyPrint as PP hiding ((<>), ($$)) | ||
94 | import Text.PrettyPrint.HughesPJClass hiding ((<>),($$)) | ||
95 | 87 | ||
96 | import Data.Torrent as Torrent | 88 | import Data.Torrent as Torrent |
97 | import Network.KRPC as KRPC hiding (Options, def) | 89 | import Network.KRPC as KRPC hiding (Options, def) |
@@ -118,7 +110,7 @@ defaultAlpha = 3 | |||
118 | 110 | ||
119 | -- TODO do not insert infohash -> peeraddr if infohash is too far from | 111 | -- TODO do not insert infohash -> peeraddr if infohash is too far from |
120 | -- this node id | 112 | -- this node id |
121 | 113 | {- | |
122 | data Order | 114 | data Order |
123 | = NearFirst | 115 | = NearFirst |
124 | | FarFirst | 116 | | FarFirst |
@@ -127,6 +119,7 @@ data Order | |||
127 | data Traversal | 119 | data Traversal |
128 | = Greedy -- ^ aggressive short-circuit traversal | 120 | = Greedy -- ^ aggressive short-circuit traversal |
129 | | Exhaustive -- ^ | 121 | | Exhaustive -- ^ |
122 | -} | ||
130 | 123 | ||
131 | -- | Original Kamelia DHT uses term /publish/ for data replication | 124 | -- | Original Kamelia DHT uses term /publish/ for data replication |
132 | -- process. BitTorrent DHT uses term /announce/ since the purpose of | 125 | -- process. BitTorrent DHT uses term /announce/ since the purpose of |
@@ -460,11 +453,11 @@ deleteTopic ih p = do | |||
460 | -- Messaging | 453 | -- Messaging |
461 | -----------------------------------------------------------------------} | 454 | -----------------------------------------------------------------------} |
462 | 455 | ||
463 | -- TODO: use alpha | ||
464 | -- | Failed queries are ignored. | 456 | -- | Failed queries are ignored. |
465 | queryParallel :: [DHT ip a] -> DHT ip [a] | 457 | queryParallel :: [DHT ip a] -> DHT ip [a] |
466 | queryParallel queries = do | 458 | queryParallel queries = do |
467 | alpha <- asks (optAlpha . options) | 459 | -- TODO: use alpha |
460 | -- alpha <- asks (optAlpha . options) | ||
468 | cleanup <$> mapConcurrently try queries | 461 | cleanup <$> mapConcurrently try queries |
469 | where | 462 | where |
470 | cleanup :: [Either QueryFailure a] -> [a] | 463 | cleanup :: [Either QueryFailure a] -> [a] |
diff --git a/src/Network/BitTorrent/DHT/Token.hs b/src/Network/BitTorrent/DHT/Token.hs index a0ed428b..7aaaf2b7 100644 --- a/src/Network/BitTorrent/DHT/Token.hs +++ b/src/Network/BitTorrent/DHT/Token.hs | |||
@@ -37,7 +37,6 @@ module Network.BitTorrent.DHT.Token | |||
37 | , Network.BitTorrent.DHT.Token.update | 37 | , Network.BitTorrent.DHT.Token.update |
38 | ) where | 38 | ) where |
39 | 39 | ||
40 | import Control.Applicative | ||
41 | import Control.Monad.State | 40 | import Control.Monad.State |
42 | import Data.BEncode (BEncode) | 41 | import Data.BEncode (BEncode) |
43 | import Data.ByteString as BS | 42 | import Data.ByteString as BS |
@@ -119,4 +118,4 @@ update TokenMap {..} = TokenMap | |||
119 | , generator = newGen | 118 | , generator = newGen |
120 | } | 119 | } |
121 | where | 120 | where |
122 | (newSecret, newGen) = next generator \ No newline at end of file | 121 | (newSecret, newGen) = next generator |