X-Git-Url: https://git.rkrishnan.org/?a=blobdiff_plain;f=src%2FFuncTorrent%2FTracker%2FHttp.hs;h=abb4b32963e8812f25071d63f9bf9a4d00821e94;hb=a533e0ed9679e77a3e50eb1786dbe3017a4e9928;hp=0cb36b9e8955ae4ec738ea2ecde6b248c99cf1f4;hpb=53d6f1e577880946a0f17d192b4c19691e486c50;p=functorrent.git diff --git a/src/FuncTorrent/Tracker/Http.hs b/src/FuncTorrent/Tracker/Http.hs index 0cb36b9..abb4b32 100644 --- a/src/FuncTorrent/Tracker/Http.hs +++ b/src/FuncTorrent/Tracker/Http.hs @@ -1,22 +1,23 @@ -{-# LANGUAGE OverloadedStrings #-} {- -Copyright (C) 2015-2016 Ramakrishnan Muthukrishnan - -This file is part of FuncTorrent. - -FuncTorrent is free software; you can redistribute it and/or modify -it under the terms of the GNU General Public License as published by -the Free Software Foundation; either version 3 of the License, or -(at your option) any later version. - -FuncTorrent is distributed in the hope that it will be useful, -but WITHOUT ANY WARRANTY; without even the implied warranty of -MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the -GNU General Public License for more details. + - Copyright (C) 2015-2016 Ramakrishnan Muthukrishnan + - + - This file is part of FuncTorrent. + - + - FuncTorrent is free software; you can redistribute it and/or modify + - it under the terms of the GNU General Public License as published by + - the Free Software Foundation; either version 3 of the License, or + - (at your option) any later version. + - + - FuncTorrent is distributed in the hope that it will be useful, + - but WITHOUT ANY WARRANTY; without even the implied warranty of + - MERCHANTABILITY or FITNESS FOR A PARTICULAR PURPOSE. See the + - GNU General Public License for more details. + - + - You should have received a copy of the GNU General Public License + - along with FuncTorrent; if not, see + -} -You should have received a copy of the GNU General Public License -along with FuncTorrent; if not, see --} +{-# LANGUAGE OverloadedStrings #-} module FuncTorrent.Tracker.Http (trackerLoop @@ -25,8 +26,8 @@ module FuncTorrent.Tracker.Http import Prelude hiding (lookup, splitAt) import Control.Concurrent (threadDelay) -import Control.Concurrent.MVar (readMVar, putMVar) -import Control.Monad (forever) +import Control.Concurrent.MVar (readMVar, putMVar, isEmptyMVar, swapMVar) +import Control.Monad (forever, void) import qualified Data.ByteString.Base16 as B16 (encode) import Data.ByteString (ByteString) import Data.ByteString.Char8 as BC (pack, unpack, splitAt) @@ -41,8 +42,8 @@ import FuncTorrent.Bencode (BVal(..)) import qualified FuncTorrent.FileSystem as FS (MsgChannel, Stats(..), getStats) import FuncTorrent.Network (sendGetRequest) import FuncTorrent.Peer (Peer(..)) -import FuncTorrent.Utils (splitN) -import FuncTorrent.Tracker.Types(TState(..), TrackerResponse(..), Port, IP) +import FuncTorrent.Utils (splitN, toIP, toPort, IP, Port) +import FuncTorrent.Tracker.Types(TState(..), TrackerResponse(..)) --- | URL encode hash as per RFC1738 @@ -80,14 +81,19 @@ trackerLoop url port peerId infohash fschan tstate = forever $ do down = FS.bytesWritten st resp <- sendGetRequest url $ mkArgs port peerId up down (left tstate) infohash case Benc.decode resp of - Left e -> return () -- $ pack (show e) + Left e -> + return () -- $ pack (show e) Right trackerInfo -> case parseTrackerResponse trackerInfo of - Left e -> return () -- e + Left e -> return () Right tresp -> do - _ <- threadDelay $ fromIntegral (interval tresp) - _ <- putMVar (connectedPeers tstate) (peers tresp) - return () -- trackerLoop port peerId st + ps <- isEmptyMVar $ connectedPeers tstate + if ps + then + putMVar (connectedPeers tstate) (peers tresp) + else + void $ swapMVar (connectedPeers tstate) (peers tresp) + threadDelay $ fromIntegral (interval tresp) parseTrackerResponse :: BVal -> Either ByteString TrackerResponse parseTrackerResponse resp = @@ -110,14 +116,3 @@ parseTrackerResponse resp = makePeer :: ByteString -> Peer makePeer peer = Peer "" (toIP ip') (toPort port') where (ip', port') = splitAt 4 peer - -toPort :: ByteString -> Port -toPort = read . ("0x" ++) . unpack . B16.encode - -toIP :: ByteString -> IP -toIP = Data.List.intercalate "." . - map (show . toInt . ("0x" ++) . unpack) . - splitN 2 . B16.encode - -toInt :: String -> Integer -toInt = read