diff options
Diffstat (limited to 'src/Network')
-rw-r--r-- | src/Network/BitTorrent/Tracker/UDP.hs | 246 |
1 files changed, 192 insertions, 54 deletions
diff --git a/src/Network/BitTorrent/Tracker/UDP.hs b/src/Network/BitTorrent/Tracker/UDP.hs index 13e1298b..23c6cacc 100644 --- a/src/Network/BitTorrent/Tracker/UDP.hs +++ b/src/Network/BitTorrent/Tracker/UDP.hs | |||
@@ -6,50 +6,93 @@ | |||
6 | -- Portability : portable | 6 | -- Portability : portable |
7 | -- | 7 | -- |
8 | -- This module implement low-level UDP tracker protocol. | 8 | -- This module implement low-level UDP tracker protocol. |
9 | -- For more info see: http://www.bittorrent.org/beps/bep_0015.html | 9 | -- For more info see: |
10 | -- <http://www.bittorrent.org/beps/bep_0015.html> | ||
10 | -- | 11 | -- |
11 | {-# LANGUAGE RecordWildCards #-} | 12 | {-# LANGUAGE RecordWildCards #-} |
12 | {-# LANGUAGE FlexibleInstances #-} | 13 | {-# LANGUAGE FlexibleInstances #-} |
13 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 14 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
14 | module Network.BitTorrent.Tracker.UDP | 15 | module Network.BitTorrent.Tracker.UDP |
15 | ( Request(..), Response(..) | 16 | ( UDPTracker |
17 | , initialTracker | ||
18 | , putTracker | ||
19 | , connectUDP | ||
20 | , freshConnection | ||
16 | ) where | 21 | ) where |
17 | 22 | ||
18 | import Control.Applicative | 23 | import Control.Applicative |
24 | import Control.Exception | ||
19 | import Control.Monad | 25 | import Control.Monad |
26 | import Data.ByteString (ByteString) | ||
27 | import Data.IORef | ||
28 | import Data.List as L | ||
29 | import Data.Maybe | ||
30 | import Data.Monoid | ||
20 | import Data.Serialize | 31 | import Data.Serialize |
21 | import Data.Word | ||
22 | import Data.Text | 32 | import Data.Text |
23 | import Data.Text.Encoding | 33 | import Data.Text.Encoding |
34 | import Data.Time | ||
35 | import Data.Word | ||
36 | import Text.Read (readMaybe) | ||
24 | import Network.Socket hiding (Connected) | 37 | import Network.Socket hiding (Connected) |
25 | import Network.Socket.ByteString as BS | 38 | import Network.Socket.ByteString as BS |
39 | import Network.URI | ||
40 | import System.Entropy | ||
41 | import Numeric | ||
26 | 42 | ||
27 | import Data.Torrent.Metainfo () | 43 | import Data.Torrent.Metainfo () |
28 | import Network.BitTorrent.Tracker.Protocol | 44 | import Network.BitTorrent.Tracker.Protocol |
29 | 45 | ||
46 | {----------------------------------------------------------------------- | ||
47 | Tokens | ||
48 | -----------------------------------------------------------------------} | ||
30 | 49 | ||
50 | genToken :: IO Word64 | ||
51 | genToken = do | ||
52 | bs <- getEntropy 8 | ||
53 | either err return $ runGet getWord64be bs | ||
54 | where | ||
55 | err = error "genToken: impossible happen" | ||
56 | |||
57 | -- TODO rename | ||
31 | -- | Connection Id is used for entire tracker session. | 58 | -- | Connection Id is used for entire tracker session. |
32 | newtype ConnId = ConnId { getConnId :: Word64 } | 59 | newtype ConnId = ConnId Word64 |
33 | deriving (Show, Eq, Serialize) | 60 | deriving (Eq, Serialize) |
34 | 61 | ||
35 | -- | Transaction Id is used for within UDP RPC. | 62 | instance Show ConnId where |
36 | newtype TransId = TransId { getTransId :: Word32 } | 63 | showsPrec _ (ConnId cid) = showString "0x" <> showHex cid |
37 | deriving (Show, Eq, Serialize) | ||
38 | 64 | ||
39 | genTransactionId :: IO TransId | 65 | genConnectionId :: IO ConnId |
40 | genTransactionId = return (TransId 0) | 66 | genConnectionId = ConnId <$> genToken |
41 | 67 | ||
42 | initialConnectionId :: ConnId | 68 | initialConnectionId :: ConnId |
43 | initialConnectionId = ConnId 0 | 69 | initialConnectionId = ConnId 0x41727101980 |
70 | |||
71 | -- TODO rename | ||
72 | -- | Transaction Id is used within a UDP RPC. | ||
73 | newtype TransId = TransId Word32 | ||
74 | deriving (Eq, Serialize) | ||
75 | |||
76 | instance Show TransId where | ||
77 | showsPrec _ (TransId tid) = showString "0x" <> showHex tid | ||
78 | |||
79 | genTransactionId :: IO TransId | ||
80 | genTransactionId = (TransId . fromIntegral) <$> genToken | ||
81 | |||
82 | {----------------------------------------------------------------------- | ||
83 | Transactions | ||
84 | -----------------------------------------------------------------------} | ||
44 | 85 | ||
45 | data Request = Connect | 86 | data Request = Connect |
46 | | Announce AnnounceQuery | 87 | | Announce AnnounceQuery |
47 | | Scrape ScrapeQuery | 88 | | Scrape ScrapeQuery |
89 | deriving Show | ||
48 | 90 | ||
49 | data Response = Connected | 91 | data Response = Connected ConnId |
50 | | Announced AnnounceInfo | 92 | | Announced AnnounceInfo |
51 | | Scraped [ScrapeInfo] | 93 | | Scraped [ScrapeInfo] |
52 | | Failed Text | 94 | | Failed Text |
95 | deriving Show | ||
53 | 96 | ||
54 | -- TODO rename to message? | 97 | -- TODO rename to message? |
55 | data Transaction a = Transaction | 98 | data Transaction a = Transaction |
@@ -70,7 +113,7 @@ instance Serialize (Transaction Request) where | |||
70 | put Transaction {..} = do | 113 | put Transaction {..} = do |
71 | case body of | 114 | case body of |
72 | Connect -> do | 115 | Connect -> do |
73 | put connId | 116 | put initialConnectionId |
74 | put connectId | 117 | put connectId |
75 | put transId | 118 | put transId |
76 | 119 | ||
@@ -82,15 +125,15 @@ instance Serialize (Transaction Request) where | |||
82 | 125 | ||
83 | Scrape hashes -> do | 126 | Scrape hashes -> do |
84 | put connId | 127 | put connId |
85 | put announceId | 128 | put scrapeId |
86 | put transId | 129 | put transId |
87 | forM_ hashes put | 130 | forM_ hashes put |
88 | 131 | ||
89 | get = do | 132 | get = do |
90 | cid <- get | 133 | cid <- get |
91 | rid <- getWord32be | 134 | mid <- getWord32be |
92 | tid <- get | 135 | tid <- get |
93 | bod <- getBody rid | 136 | bod <- getBody mid |
94 | 137 | ||
95 | return $ Transaction { | 138 | return $ Transaction { |
96 | connId = cid | 139 | connId = cid |
@@ -100,7 +143,7 @@ instance Serialize (Transaction Request) where | |||
100 | where | 143 | where |
101 | getBody :: MessageId -> Get Request | 144 | getBody :: MessageId -> Get Request |
102 | getBody msgId | 145 | getBody msgId |
103 | | msgId == connectId = return Connect | 146 | | msgId == connectId = pure Connect |
104 | | msgId == announceId = Announce <$> get | 147 | | msgId == announceId = Announce <$> get |
105 | | msgId == scrapeId = Scrape <$> many get | 148 | | msgId == scrapeId = Scrape <$> many get |
106 | | otherwise = fail "unknown message id" | 149 | | otherwise = fail "unknown message id" |
@@ -108,45 +151,42 @@ instance Serialize (Transaction Request) where | |||
108 | instance Serialize (Transaction Response) where | 151 | instance Serialize (Transaction Response) where |
109 | put Transaction {..} = do | 152 | put Transaction {..} = do |
110 | case body of | 153 | case body of |
111 | Connected -> do | 154 | Connected conn -> do |
112 | put connId | ||
113 | put connectId | 155 | put connectId |
114 | put transId | 156 | put transId |
157 | put conn | ||
115 | 158 | ||
116 | Announced info -> do | 159 | Announced info -> do |
117 | put connId | ||
118 | put announceId | 160 | put announceId |
119 | put transId | 161 | put transId |
120 | put info | 162 | put info |
121 | 163 | ||
122 | Scraped infos -> do | 164 | Scraped infos -> do |
123 | put connId | ||
124 | put scrapeId | 165 | put scrapeId |
125 | put transId | 166 | put transId |
126 | forM_ infos put | 167 | forM_ infos put |
127 | 168 | ||
128 | Failed info -> do | 169 | Failed info -> do |
129 | put connId | ||
130 | put errorId | 170 | put errorId |
131 | put transId | 171 | put transId |
132 | put (encodeUtf8 info) | 172 | put (encodeUtf8 info) |
133 | 173 | ||
134 | 174 | ||
135 | get = do | 175 | get = do |
136 | cid <- get | 176 | -- cid <- get |
137 | rid <- getWord32be | 177 | mid <- getWord32be |
138 | tid <- get | 178 | tid <- get |
139 | bod <- getBody rid | 179 | bod <- getBody mid |
140 | 180 | ||
141 | return $ Transaction { | 181 | return $ Transaction { |
142 | connId = cid | 182 | connId = initialConnectionId -- TODO |
143 | , transId = tid | 183 | , transId = tid |
144 | , body = bod | 184 | , body = bod |
145 | } | 185 | } |
146 | where | 186 | where |
147 | getBody :: MessageId -> Get Response | 187 | getBody :: MessageId -> Get Response |
148 | getBody msgId | 188 | getBody msgId |
149 | | msgId == connectId = return $ Connected | 189 | | msgId == connectId = Connected <$> get |
150 | | msgId == announceId = Announced <$> get | 190 | | msgId == announceId = Announced <$> get |
151 | | msgId == scrapeId = Scraped <$> many get | 191 | | msgId == scrapeId = Scraped <$> many get |
152 | | msgId == errorId = do | 192 | | msgId == errorId = do |
@@ -154,38 +194,136 @@ instance Serialize (Transaction Response) where | |||
154 | case decodeUtf8' bs of | 194 | case decodeUtf8' bs of |
155 | Left ex -> fail (show ex) | 195 | Left ex -> fail (show ex) |
156 | Right msg -> return $ Failed msg | 196 | Right msg -> return $ Failed msg |
157 | | otherwise = fail "unknown message id" | 197 | | otherwise = fail $ "unknown message id: " ++ show msgId |
158 | 198 | ||
159 | maxPacketSize :: Int | 199 | {----------------------------------------------------------------------- |
160 | maxPacketSize = 98 -- announce request packet | 200 | Connection |
201 | -----------------------------------------------------------------------} | ||
161 | 202 | ||
162 | call :: Request -> IO Response | 203 | connectionLifetime :: NominalDiffTime |
163 | call request = do | 204 | connectionLifetime = 60 |
164 | tid <- genTransactionId | 205 | |
165 | let trans = Transaction initialConnectionId tid request | 206 | connectionLifetimeServer :: NominalDiffTime |
166 | 207 | connectionLifetimeServer = 120 | |
167 | let addr = error "TODO" | ||
168 | sock <- socket AF_INET Datagram defaultProtocol | ||
169 | BS.sendAllTo sock (encode trans) addr | ||
170 | (resp, addr') <- BS.recvFrom sock 4096 | ||
171 | if addr' /= addr | ||
172 | then error "address mismatch" | ||
173 | else case decode resp of | ||
174 | Left msg -> error msg | ||
175 | Right (Transaction {..}) -> do | ||
176 | if tid /= transId | ||
177 | then error "transaction id mismatch" | ||
178 | else return body | ||
179 | 208 | ||
180 | data Connection = Connection | 209 | data Connection = Connection |
210 | { connectionId :: ConnId | ||
211 | , connectionTimestamp :: UTCTime | ||
212 | } deriving Show | ||
213 | |||
214 | initialConnection :: IO Connection | ||
215 | initialConnection = Connection initialConnectionId <$> getCurrentTime | ||
181 | 216 | ||
182 | type URI = () | 217 | isExpired :: Connection -> IO Bool |
218 | isExpired Connection {..} = do | ||
219 | currentTime <- getCurrentTime | ||
220 | let timeDiff = diffUTCTime currentTime connectionTimestamp | ||
221 | return $ timeDiff > connectionLifetime | ||
183 | 222 | ||
184 | connectTracker :: URI -> IO Connection | 223 | {----------------------------------------------------------------------- |
185 | connectTracker = undefined | 224 | RPC |
225 | -----------------------------------------------------------------------} | ||
186 | 226 | ||
187 | announceTracker :: Connection -> AnnounceQuery -> IO AnnounceInfo | 227 | maxPacketSize :: Int |
188 | announceTracker = undefined | 228 | maxPacketSize = 98 -- announce request packet |
189 | 229 | ||
190 | scrape :: Connection -> ScrapeQuery -> IO [ScrapeInfo] | 230 | setPort :: PortNumber -> SockAddr -> SockAddr |
191 | scrape = undefined \ No newline at end of file | 231 | setPort p (SockAddrInet _ h) = SockAddrInet p h |
232 | setPort p (SockAddrInet6 _ f h s) = SockAddrInet6 p f h s | ||
233 | setPort _ addr = addr | ||
234 | |||
235 | getTrackerAddr :: URI -> IO SockAddr | ||
236 | getTrackerAddr URI { uriAuthority = Just (URIAuth {..}) } = do | ||
237 | infos <- getAddrInfo Nothing (Just uriRegName) Nothing | ||
238 | let port = fromMaybe 0 (readMaybe (L.drop 1 uriPort) :: Maybe Int) | ||
239 | case infos of | ||
240 | AddrInfo {..} : _ -> return $ setPort (fromIntegral port) addrAddress | ||
241 | _ -> fail "getTrackerAddr: unable to lookup host addr" | ||
242 | getTrackerAddr _ = fail "getTrackerAddr: hostname unknown" | ||
243 | |||
244 | call :: SockAddr -> ByteString -> IO ByteString | ||
245 | call addr arg = bracket open close rpc | ||
246 | where | ||
247 | open = socket AF_INET Datagram defaultProtocol | ||
248 | rpc sock = do | ||
249 | BS.sendAllTo sock arg addr | ||
250 | (res, addr') <- BS.recvFrom sock maxPacketSize | ||
251 | unless (addr' == addr) $ do | ||
252 | throwIO $ userError "address mismatch" | ||
253 | return res | ||
254 | |||
255 | -- TODO retransmissions | ||
256 | -- TODO blocking | ||
257 | data UDPTracker = UDPTracker | ||
258 | { trackerURI :: URI | ||
259 | , trackerConnection :: IORef Connection | ||
260 | } | ||
261 | |||
262 | updateConnection :: ConnId -> UDPTracker -> IO () | ||
263 | updateConnection cid UDPTracker {..} = do | ||
264 | newConnection <- Connection cid <$> getCurrentTime | ||
265 | writeIORef trackerConnection newConnection | ||
266 | |||
267 | getConnectionId :: UDPTracker -> IO ConnId | ||
268 | getConnectionId UDPTracker {..} | ||
269 | = connectionId <$> readIORef trackerConnection | ||
270 | |||
271 | putTracker :: UDPTracker -> IO () | ||
272 | putTracker UDPTracker {..} = do | ||
273 | print trackerURI | ||
274 | print =<< readIORef trackerConnection | ||
275 | |||
276 | transaction :: UDPTracker -> Request -> IO (Transaction Response) | ||
277 | transaction tracker @ UDPTracker {..} request = do | ||
278 | cid <- getConnectionId tracker | ||
279 | tid <- genTransactionId | ||
280 | let trans = Transaction cid tid request | ||
281 | |||
282 | addr <- getTrackerAddr trackerURI | ||
283 | res <- call addr (encode trans) | ||
284 | case decode res of | ||
285 | Right (response @ Transaction {..}) | ||
286 | | tid == transId -> return response | ||
287 | | otherwise -> throwIO $ userError "transaction id mismatch" | ||
288 | Left msg -> throwIO $ userError msg | ||
289 | |||
290 | connectUDP :: UDPTracker -> IO ConnId | ||
291 | connectUDP tracker = do | ||
292 | Transaction _ tid resp <- transaction tracker Connect | ||
293 | case resp of | ||
294 | Connected cid -> return cid | ||
295 | |||
296 | initialTracker :: URI -> IO UDPTracker | ||
297 | initialTracker uri = do | ||
298 | tracker <- UDPTracker uri <$> (newIORef =<< initialConnection) | ||
299 | connId <- connectUDP tracker | ||
300 | updateConnection connId tracker | ||
301 | return tracker | ||
302 | |||
303 | freshConnection :: UDPTracker -> IO () | ||
304 | freshConnection tracker @ UDPTracker {..} = do | ||
305 | conn <- readIORef trackerConnection | ||
306 | expired <- isExpired conn | ||
307 | when expired $ do | ||
308 | connId <- connectUDP tracker | ||
309 | updateConnection connId tracker | ||
310 | |||
311 | {- | ||
312 | |||
313 | announceUDP :: UDPTracker -> AnnounceQuery -> IO AnnounceInfo | ||
314 | announceUDP t query = do | ||
315 | Transaction tid cid resp <- call transaction (Announce query) | ||
316 | case resp of | ||
317 | Announced info -> return info | ||
318 | _ -> fail "response type mismatch" | ||
319 | |||
320 | scrapeUDP :: UDPTracker -> ScrapeQuery -> IO Scrape | ||
321 | scrapeUDP UDPTracker {..} query = do | ||
322 | resp <- call trackerURI $ Scrape query | ||
323 | case resp of | ||
324 | Scraped scrape -> return undefined | ||
325 | |||
326 | instance Tracker UDPTracker where | ||
327 | announce = announceUDP | ||
328 | scrape_ = scrapeUDP | ||
329 | -} \ No newline at end of file | ||