summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/DHT/Query.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/DHT/Query.hs')
-rw-r--r--src/Network/BitTorrent/DHT/Query.hs36
1 files changed, 36 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/DHT/Query.hs b/src/Network/BitTorrent/DHT/Query.hs
index 8215c95d..39ef9604 100644
--- a/src/Network/BitTorrent/DHT/Query.hs
+++ b/src/Network/BitTorrent/DHT/Query.hs
@@ -13,6 +13,7 @@
13{-# LANGUAGE FlexibleContexts #-} 13{-# LANGUAGE FlexibleContexts #-}
14{-# LANGUAGE ScopedTypeVariables #-} 14{-# LANGUAGE ScopedTypeVariables #-}
15{-# LANGUAGE TemplateHaskell #-} 15{-# LANGUAGE TemplateHaskell #-}
16{-# LANGUAGE TupleSections #-}
16module Network.BitTorrent.DHT.Query 17module Network.BitTorrent.DHT.Query
17 ( -- * Handler 18 ( -- * Handler
18 -- | To bind specific set of handlers you need to pass 19 -- | To bind specific set of handlers you need to pass
@@ -40,6 +41,9 @@ module Network.BitTorrent.DHT.Query
40 , Search 41 , Search
41 , search 42 , search
42 , publish 43 , publish
44 , ioFindNode
45 , ioGetPeers
46 , isearch
43 47
44 -- ** Routing table 48 -- ** Routing table
45 , insertNode 49 , insertNode
@@ -67,6 +71,8 @@ import Data.Either
67import Data.List as L 71import Data.List as L
68import Data.Monoid 72import Data.Monoid
69import Data.Text as T 73import Data.Text as T
74import qualified Data.Set as Set
75 ;import Data.Set (Set)
70import Network 76import Network
71import Text.PrettyPrint as PP hiding ((<>), ($$)) 77import Text.PrettyPrint as PP hiding ((<>), ($$))
72import Text.PrettyPrint.HughesPJClass hiding ((<>),($$)) 78import Text.PrettyPrint.HughesPJClass hiding ((<>),($$))
@@ -82,6 +88,7 @@ import Network.BitTorrent.DHT.Message
82import Network.BitTorrent.DHT.Routing as R 88import Network.BitTorrent.DHT.Routing as R
83import Network.BitTorrent.DHT.Session 89import Network.BitTorrent.DHT.Session
84import Control.Concurrent.STM 90import Control.Concurrent.STM
91import qualified Network.BitTorrent.DHT.Search as Search
85 92
86{----------------------------------------------------------------------- 93{-----------------------------------------------------------------------
87-- Handlers 94-- Handlers
@@ -182,6 +189,35 @@ announceQ ih p NodeInfo {..} = do
182-- Iterative queries 189-- Iterative queries
183-----------------------------------------------------------------------} 190-----------------------------------------------------------------------}
184 191
192
193ioGetPeers :: Address ip => InfoHash -> DHT ip (NodeInfo ip -> IO ([NodeInfo ip], [PeerAddr ip]))
194ioGetPeers ih = do
195 session <- ask
196 return $ \ni -> runDHT session $ do
197 r <- try $ getPeersQ ih ni
198 case r of
199 Right e -> return $ either (,[]) ([],) e
200 Left e -> let _ = e :: QueryFailure in return ([],[])
201
202ioFindNode :: Address ip => InfoHash -> DHT ip (NodeInfo ip -> IO ([NodeInfo ip], [NodeInfo ip]))
203ioFindNode ih = do
204 session <- ask
205 return $ \ni -> runDHT session $ do
206 NodeFound ns <- FindNode (toNodeId ih) <@> nodeAddr ni
207 return $ L.partition (\n -> nodeId n /= toNodeId ih) ns
208
209isearch :: (Ord r, Ord ip) =>
210 (InfoHash -> DHT ip (NodeInfo ip -> IO ([NodeInfo ip], [r])))
211 -> InfoHash
212 -> DHT ip (Set r)
213isearch f ih = do
214 qry <- f ih
215 ns <- kclosest 8 ih <$> getTable
216 liftIO $ do s <- Search.newSearch qry (toNodeId ih) ns
217 Search.search s
218 atomically $ readTVar (Search.searchResults s)
219
220
185type Search ip o = Conduit [NodeInfo ip] (DHT ip) [o ip] 221type Search ip o = Conduit [NodeInfo ip] (DHT ip) [o ip]
186 222
187-- TODO: use reorder and filter (Traversal option) leftovers 223-- TODO: use reorder and filter (Traversal option) leftovers