]> git.rkrishnan.org Git - functorrent.git/blob - src/FuncTorrent/Tracker/Http.hs
refactor: remove peerid from Peer datatype
[functorrent.git] / src / FuncTorrent / Tracker / Http.hs
1 {-
2  - Copyright (C) 2015-2016 Ramakrishnan Muthukrishnan <ram@rkrishnan.org>
3  -
4  - This file is part of FuncTorrent.
5  -
6  - FuncTorrent is free software; you can redistribute it and/or modify
7  - it under the terms of the GNU General Public License as published by
8  - the Free Software Foundation; either version 3 of the License, or
9  - (at your option) any later version.
10  -
11  - FuncTorrent is distributed in the hope that it will be useful,
12  - but WITHOUT ANY WARRANTY; without even the implied warranty of
13  - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE.  See the
14  - GNU General Public License for more details.
15  -
16  - You should have received a copy of the GNU General Public License
17  - along with FuncTorrent; if not,  see <http://www.gnu.org/licenses/>
18  -}
19
20 {-# LANGUAGE OverloadedStrings #-}
21
22 module FuncTorrent.Tracker.Http
23        (trackerLoop
24        ) where
25
26 import Prelude hiding (lookup)
27
28 import Control.Concurrent (threadDelay)
29 import Control.Concurrent.MVar (readMVar, putMVar, isEmptyMVar, swapMVar)
30 import Control.Monad (forever, void)
31 import qualified Data.ByteString.Base16 as B16 (encode)
32 import Data.ByteString (ByteString)
33 import Data.ByteString.Char8 as BC (pack, unpack)
34 import Data.Char (chr)
35 import Data.Map as M (lookup)
36 import Network (PortNumber)
37 import Network.HTTP.Base (urlEncode)
38
39 import qualified FuncTorrent.Bencode as Benc
40 import FuncTorrent.Bencode (BVal(..))
41 import qualified FuncTorrent.FileSystem as FS (MsgChannel, Stats(..), getStats)
42 import FuncTorrent.Network (sendGetRequest)
43 import FuncTorrent.PeerMsgs (makePeer)
44 import FuncTorrent.Utils (splitN, IP, Port)
45 import FuncTorrent.Tracker.Types(TState(..), TrackerResponse(..))
46
47
48 --- | URL encode hash as per RFC1738
49 --- TODO: Add tests
50 --- REVIEW: Why is this not written in terms of `Network.HTTP.Base.urlEncode` or
51 --- equivalent library function?
52 urlEncodeHash :: ByteString -> String
53 urlEncodeHash bs = concatMap (encode' . unpack) (splitN 2 bs)
54   where encode' b@[c1, c2] = let c =  chr (read ("0x" ++ b))
55                             in escape c c1 c2
56         encode' _ = ""
57         escape i c1 c2 | i `elem` nonSpecialChars = [i]
58                        | otherwise = "%" ++ [c1] ++ [c2]
59
60         nonSpecialChars = ['A'..'Z'] ++ ['a'..'z'] ++ ['0'..'9'] ++ "-_.~"
61
62 -- | Make arguments that should be posted to tracker.
63 -- This is a separate pure function for testability.
64 mkArgs :: PortNumber -> String -> Integer -> Integer -> Integer -> ByteString -> [(String, ByteString)]
65 mkArgs port peer_id up down left' infoHash =
66   [("info_hash", pack . urlEncodeHash . B16.encode $ infoHash),
67    ("peer_id", pack . urlEncode $ peer_id),
68    ("port", pack $ show port),
69    ("uploaded", pack $ show up),
70    ("downloaded", pack $ show down),
71    ("left", pack $ show left'),
72    ("compact", "1"),
73    ("event", "started")]
74
75 trackerLoop :: String -> PortNumber -> String -> ByteString -> FS.MsgChannel -> TState -> IO ()
76 trackerLoop url sport peerId infohash fschan tstate = forever $ do
77   st <- readMVar <$> FS.getStats fschan
78   up <- fmap FS.bytesRead st
79   down <- fmap FS.bytesWritten st
80   resp <- sendGetRequest url $ mkArgs sport peerId up down (left tstate) infohash
81   case Benc.decode resp of
82     Left e ->
83       return () -- $ pack (show e)
84     Right trackerInfo ->
85       case parseTrackerResponse trackerInfo of
86         Left e -> return ()
87         Right tresp -> do
88           ps <- isEmptyMVar $ connectedPeers tstate
89           if ps
90             then
91             putMVar (connectedPeers tstate) (peers tresp)
92             else
93             void $ swapMVar (connectedPeers tstate) (peers tresp)
94           threadDelay $ fromIntegral (interval tresp)
95
96 parseTrackerResponse :: BVal -> Either ByteString TrackerResponse
97 parseTrackerResponse resp =
98     case lookup "failure reason" body of
99       Just (Bstr err) -> Left err
100       Just _ -> Left "Unknown failure"
101       Nothing ->
102           let (Just (Bint i)) = lookup "interval" body
103               (Just (Bstr peersBS)) = lookup "peers" body
104               pl = map makePeer (splitN 6 peersBS)
105           in Right TrackerResponse {
106                    interval = i
107                  , peers = pl
108                  , complete = Nothing
109                  , incomplete = Nothing
110                  }
111     where
112       (Bdict body) = resp
113