]> git.rkrishnan.org Git - functorrent.git/blob - src/Tracker.hs
Make network request return ByteString
[functorrent.git] / src / Tracker.hs
1 module Tracker where
2
3 import Prelude hiding (lookup)
4
5 import Bencode (BVal(..), InfoDict, encode)
6 import Crypto.Hash.SHA1 (hash)
7 import Data.ByteString.Char8 (ByteString, pack, unpack)
8 import Data.Char (chr)
9 import Data.List (intercalate)
10 import Data.Maybe (fromJust)
11 import Data.Map as M (Map, (!))
12 import Network.HTTP (simpleHTTP, defaultGETRequest_, getResponseBody)
13 import Network.HTTP.Base (urlEncode)
14 import Network.URI (parseURI)
15 import Utils (splitN)
16 import qualified Data.ByteString.Base16 as B16 (encode)
17
18 type Url = String
19
20 -- | urlEncodeHash
21 --
22 -- >>> urlEncodeHash $ pack "123456789abcdef123456789abcdef123456789a"
23 -- "%124Vx%9a%bc%de%f1%23Eg%89%ab%cd%ef%124Vx%9a"
24 urlEncodeHash :: ByteString -> String
25 urlEncodeHash bs = concatMap (encode' . unpack) (splitN 2 bs)
26   where encode' b@[c1, c2] = let c =  chr (read ("0x" ++ b))
27                             in escape c c1 c2
28         encode' _ = ""
29         escape i c1 c2 | i `elem` nonSpecialChars = [i]
30                        | otherwise = "%" ++ [c1] ++ [c2]
31
32         nonSpecialChars = ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ "-_.~"
33
34 infoHash :: Map BVal BVal -> ByteString
35 infoHash m = let info = m ! Bstr (pack "info")
36              in (hash . pack . encode) info
37
38 prepareRequest :: InfoDict -> String -> Integer -> String
39 prepareRequest d peer_id len =
40   let p = [("info_hash", urlEncodeHash ((B16.encode . infoHash) d)),
41            ("peer_id", urlEncode peer_id),
42            ("port", "6881"),
43            ("uploaded", "0"),
44            ("downloaded", "0"),
45            ("left", show len),
46            ("compact", "1"),
47            ("event", "started")]
48   in intercalate "&" [f ++ "=" ++ s | (f,s) <- p]
49
50 connect :: Url -> String -> IO ByteString
51 connect baseurl qstr = simpleHTTP (defaultGETRequest_ url) >>= getResponseBody
52     where url = fromJust . parseURI $ (baseurl ++ "?" ++ qstr)