summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/Exchange/Session/Metadata.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/Exchange/Session/Metadata.hs')
-rw-r--r--src/Network/BitTorrent/Exchange/Session/Metadata.hs93
1 files changed, 93 insertions, 0 deletions
diff --git a/src/Network/BitTorrent/Exchange/Session/Metadata.hs b/src/Network/BitTorrent/Exchange/Session/Metadata.hs
new file mode 100644
index 00000000..7e14f493
--- /dev/null
+++ b/src/Network/BitTorrent/Exchange/Session/Metadata.hs
@@ -0,0 +1,93 @@
1{-# LANGUAGE TemplateHaskell #-}
2module Network.BitTorrent.Exchange.Session.Metadata
3 ( -- * Metadata transfer state
4 Status
5 , nullStatus
6
7 -- * Metadata updates
8 , Updates
9 , runUpdates
10
11 -- * Metadata piece control
12 , scheduleBlock
13 , resetPending
14 , cancelPending
15 , pushBlock
16 ) where
17
18import Control.Concurrent
19import Control.Lens
20import Control.Monad.State
21import Data.ByteString as BS
22import Data.ByteString.Lazy as BL
23import Data.List as L
24
25import Data.BEncode as BE
26import Data.Torrent
27import Data.Torrent.InfoHash
28import Data.Torrent.Piece as Torrent
29import Network.BitTorrent.Core
30import Network.BitTorrent.Exchange.Block as Block
31import Network.BitTorrent.Exchange.Message as Message hiding (Status)
32
33
34data Status = Status
35 { _pending :: [(PeerAddr IP, PieceIx)]
36 , _bucket :: Bucket
37 }
38
39makeLenses ''Status
40
41nullStatus :: PieceSize -> Status
42nullStatus ps = Status [] (Block.empty ps)
43
44type Updates a = State Status a
45
46runUpdates :: MVar Status -> Updates a -> IO a
47runUpdates v m = undefined
48
49scheduleBlock :: PeerAddr IP -> Updates (Maybe PieceIx)
50scheduleBlock addr = do
51 bkt <- use bucket
52 case spans metadataPieceSize bkt of
53 [] -> return Nothing
54 ((off, _ ) : _) -> do
55 let pix = undefined
56 pending %= ((addr, pix) :)
57 return (Just pix)
58
59cancelPending :: PieceIx -> Updates ()
60cancelPending pix = pending %= L.filter ((pix ==) . snd)
61
62resetPending :: PeerAddr IP -> Updates ()
63resetPending addr = pending %= L.filter ((addr ==) . fst)
64
65parseInfoDict :: BS.ByteString -> InfoHash -> Result InfoDict
66parseInfoDict chunk topic =
67 case BE.decode chunk of
68 Right (infodict @ InfoDict {..})
69 | topic == idInfoHash -> return infodict
70 | otherwise -> Left "broken infodict"
71 Left err -> Left $ "unable to parse infodict " ++ err
72
73-- todo use incremental parsing to avoid BS.concat call
74pushBlock :: PeerAddr IP -> Torrent.Piece BS.ByteString -> InfoHash
75 -> Updates (Maybe InfoDict)
76pushBlock addr Torrent.Piece {..} topic = do
77 p <- use pending
78 when ((addr, pieceIndex) `L.notElem` p) $ error "not requested"
79 cancelPending pieceIndex
80
81 bucket %= Block.insert (metadataPieceSize * pieceIndex) pieceData
82 b <- use bucket
83 case toPiece b of
84 Nothing -> return Nothing
85 Just chunks ->
86 case parseInfoDict (BL.toStrict chunks) topic of
87 Right x -> do
88 pending .= []
89 return (Just x)
90 Left e -> do
91 pending .= []
92 bucket .= Block.empty (Block.size b)
93 return Nothing