summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--bittorrent.cabal7
-rw-r--r--examples/dht.hs17
-rw-r--r--examples/dhtd.hs24
-rw-r--r--src/Network/BitTorrent/DHT/Query.hs10
4 files changed, 42 insertions, 16 deletions
diff --git a/bittorrent.cabal b/bittorrent.cabal
index f6559752..a8858abd 100644
--- a/bittorrent.cabal
+++ b/bittorrent.cabal
@@ -89,10 +89,10 @@ library
89 Network.BitTorrent.DHT.Token 89 Network.BitTorrent.DHT.Token
90 Network.StreamServer 90 Network.StreamServer
91 Network.SocketLike 91 Network.SocketLike
92 other-modules: Paths_bittorrent
93 Data.Wrapper.PSQ
94 Data.MinMaxPSQ
95 Network.BitTorrent.DHT.Search 92 Network.BitTorrent.DHT.Search
93 Data.MinMaxPSQ
94 Data.Wrapper.PSQ
95 other-modules: Paths_bittorrent
96 if !flag(dht-only) 96 if !flag(dht-only)
97 exposed-modules: Network.BitTorrent 97 exposed-modules: Network.BitTorrent
98 Network.BitTorrent.Client 98 Network.BitTorrent.Client
@@ -377,6 +377,7 @@ executable dhtd
377 , bittorrent 377 , bittorrent
378 , unix 378 , unix
379 , containers 379 , containers
380 , stm
380 if flag(thread-debug) 381 if flag(thread-debug)
381 build-depends: time 382 build-depends: time
382 cpp-options: -DTHREAD_DEBUG 383 cpp-options: -DTHREAD_DEBUG
diff --git a/examples/dht.hs b/examples/dht.hs
index feeee9ff..16b12678 100644
--- a/examples/dht.hs
+++ b/examples/dht.hs
@@ -1,6 +1,6 @@
1{-# LANGUAGE NondecreasingIndentation #-} 1{-# LANGUAGE NondecreasingIndentation #-}
2import Control.Monad 2import Control.Monad
3import Control.Monad.Fix 3import Data.Function
4import Control.Monad.IO.Class 4import Control.Monad.IO.Class
5import Data.Char 5import Data.Char
6import Network.Socket as Socket 6import Network.Socket as Socket
@@ -34,16 +34,21 @@ hReadInt h = do
34-- and /.../ is the sequence of characters 34-- and /.../ is the sequence of characters
35-- 35--
36-- Note: The first byte after the count is ignored and discarded. 36-- Note: The first byte after the count is ignored and discarded.
37readResponse :: Handle -> IO String 37readResponse :: Handle -> IO (Char, String)
38readResponse h = do 38readResponse h = do
39 c <- hGetChar h
39 n <- hReadInt h 40 n <- hReadInt h
40 sequence $ replicate n (hGetChar h) 41 s <- sequence $ replicate n (hGetChar h)
42 return (c,s)
41 43
42-- | Send a command to the dhtd daemon and then print the response. 44-- | Send a command to the dhtd daemon and then print the response.
43sendCommand :: Handle -> String -> InputT IO () 45sendCommand :: Handle -> String -> InputT IO ()
44sendCommand h cmd = do resp <- liftIO $ do hPutStrLn h cmd 46sendCommand h cmd = do liftIO $ hPutStrLn h cmd
45 readResponse h 47 fix $ \again -> do
46 outputStrLn resp 48 (c, resp) <- liftIO $ readResponse h
49 if c /= '.'
50 then outputStr resp >> again
51 else outputStrLn resp
47 52
48-- | Get one line of input and send it to the daemon, then run the 53-- | Get one line of input and send it to the daemon, then run the
49-- passed continuation if it wasn't "quit". 54-- passed continuation if it wasn't "quit".
diff --git a/examples/dhtd.hs b/examples/dhtd.hs
index 1b02a37a..68074e2b 100644
--- a/examples/dhtd.hs
+++ b/examples/dhtd.hs
@@ -33,6 +33,7 @@ import System.Mem
33import Data.Torrent (InfoHash) 33import Data.Torrent (InfoHash)
34import Network.BitTorrent.Address 34import Network.BitTorrent.Address
35import Network.BitTorrent.DHT 35import Network.BitTorrent.DHT
36import Network.BitTorrent.DHT.Search
36import Network.BitTorrent.DHT.Query 37import Network.BitTorrent.DHT.Query
37import Network.BitTorrent.DHT.Message (FindNode(..),NodeFound(..),GetPeers(..),GotPeers(..)) 38import Network.BitTorrent.DHT.Message (FindNode(..),NodeFound(..),GetPeers(..),GotPeers(..))
38import Network.KRPC.Manager (QueryFailure(..)) 39import Network.KRPC.Manager (QueryFailure(..))
@@ -49,6 +50,7 @@ import Data.Time.Clock
49#else 50#else
50import Control.Concurrent 51import Control.Concurrent
51#endif 52#endif
53import Control.Concurrent.STM
52import System.Environment 54import System.Environment
53 55
54mkNodeAddr :: SockAddr -> NodeAddr IPv4 56mkNodeAddr :: SockAddr -> NodeAddr IPv4
@@ -130,7 +132,10 @@ marshalForClient :: String -> String
130marshalForClient s = show (length s) ++ ":" ++ s 132marshalForClient s = show (length s) ++ ":" ++ s
131 133
132hPutClient :: Handle -> String -> IO () 134hPutClient :: Handle -> String -> IO ()
133hPutClient h s = hPutStr h (marshalForClient s) 135hPutClient h s = hPutStr h ('.' : marshalForClient s)
136
137hPutClientChunk :: Handle -> String -> IO ()
138hPutClientChunk h s = hPutStr h (' ' : marshalForClient s)
134 139
135clientSession :: Node IPv4 -> MVar () -> RestrictedSocket -> Int -> Handle -> IO () 140clientSession :: Node IPv4 -> MVar () -> RestrictedSocket -> Int -> Handle -> IO ()
136clientSession st signalQuit sock n h = do 141clientSession st signalQuit sock n h = do
@@ -280,9 +285,20 @@ clientSession st signalQuit sock n h = do
280 ("search-peers", s) -> cmd $ do 285 ("search-peers", s) -> cmd $ do
281 case readEither s of 286 case readEither s of
282 Right ih -> do 287 Right ih -> do
283 ps <- Set.toList <$> isearch ioGetPeers ih 288 (tid, s) <- isearch ioGetPeers ih
284 return $ do 289 flip fix Set.empty $ \again shown -> do
285 hPutClient h $ unlines $ map (show . pPrint) ps 290 (chk,fin) <- liftIO . atomically $ do
291 r <- (Set.\\ shown) <$> readTVar (searchResults s)
292 if not $ Set.null r
293 then (,) r <$> searchIsFinished s
294 else searchIsFinished s >>= check >> return (Set.empty,True)
295 let ps = case Set.toList chk of
296 [] -> ""
297 _ -> unlines $ map (show . pPrint) $ Set.toList chk
298 if fin then return $ hPutClient h ps
299 else do
300 liftIO $ hPutClientChunk h ps
301 again (shown `Set.union` chk)
286 Left er -> return $ hPutClient h er 302 Left er -> return $ hPutClient h er
287 303
288 _ -> cmd0 $ hPutClient h "error." 304 _ -> cmd0 $ hPutClient h "error."
diff --git a/src/Network/BitTorrent/DHT/Query.hs b/src/Network/BitTorrent/DHT/Query.hs
index 39ef9604..5345f8b1 100644
--- a/src/Network/BitTorrent/DHT/Query.hs
+++ b/src/Network/BitTorrent/DHT/Query.hs
@@ -209,13 +209,17 @@ ioFindNode ih = do
209isearch :: (Ord r, Ord ip) => 209isearch :: (Ord r, Ord ip) =>
210 (InfoHash -> DHT ip (NodeInfo ip -> IO ([NodeInfo ip], [r]))) 210 (InfoHash -> DHT ip (NodeInfo ip -> IO ([NodeInfo ip], [r])))
211 -> InfoHash 211 -> InfoHash
212 -> DHT ip (Set r) 212 -> DHT ip (ThreadId, Search.IterativeSearch ip r)
213isearch f ih = do 213isearch f ih = do
214 qry <- f ih 214 qry <- f ih
215 ns <- kclosest 8 ih <$> getTable 215 ns <- kclosest 8 ih <$> getTable
216 liftIO $ do s <- Search.newSearch qry (toNodeId ih) ns 216 liftIO $ do s <- Search.newSearch qry (toNodeId ih) ns
217 Search.search s 217 a <- fork $ do
218 atomically $ readTVar (Search.searchResults s) 218 tid <- myThreadId
219 labelThread tid ("search."++show ih)
220 Search.search s
221 -- atomically $ readTVar (Search.searchResults s)
222 return (a, s)
219 223
220 224
221type Search ip o = Conduit [NodeInfo ip] (DHT ip) [o ip] 225type Search ip o = Conduit [NodeInfo ip] (DHT ip) [o ip]