summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Network/BitTorrent/Exchange/Assembler.hs154
1 files changed, 124 insertions, 30 deletions
diff --git a/src/Network/BitTorrent/Exchange/Assembler.hs b/src/Network/BitTorrent/Exchange/Assembler.hs
index b1a80c9b..5dc7c5ca 100644
--- a/src/Network/BitTorrent/Exchange/Assembler.hs
+++ b/src/Network/BitTorrent/Exchange/Assembler.hs
@@ -1,65 +1,159 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- Assembler is used to build pieces from blocks. In general
9-- 'Assembler' should be used to handle 'Transfer' messages when
10--
11-- A block can have one of the following status:
12--
13-- 1) /not allowed/: Piece is not in download set. 'null' and 'empty'.
14--
15--
16-- 2) /waiting/: (allowed?) Block have been allowed to download,
17-- but /this/ peer did not send any 'Request' message for this
18-- block. To allow some piece use
19-- 'Network.BitTorrent.Exchange.Selector' and then 'allowedSet'
20-- and 'allowPiece'.
21--
22-- 3) /inflight/: (pending?) Block have been requested but
23-- /remote/ peer did not send any 'Piece' message for this block.
24-- Related functions 'markInflight'
25--
26-- 4) /pending/: (stalled?) Block have have been downloaded
27-- Related functions 'insertBlock'.
28--
29-- Piece status:
30--
31-- 1) /assembled/: (downloaded?) All blocks in piece have been
32-- downloaded but the piece did not verified yet.
33--
34-- * Valid: go to completed;
35--
36-- * Invalid: go to waiting.
37--
38-- 2) /corrupted/:
39--
40-- 3) /downloaded/: (verified?) A piece have been successfully
41-- verified via the hash. Usually the piece should be stored to
42-- the 'System.Torrent.Storage' and /this/ peer should send 'Have'
43-- messages to the /remote/ peers.
44--
45{-# LANGUAGE TemplateHaskell #-}
1module Network.BitTorrent.Exchange.Assembler 46module Network.BitTorrent.Exchange.Assembler
2 ( Assembler 47 ( -- * Assembler
48 Assembler
49
50 -- * Query
51 , Network.BitTorrent.Exchange.Assembler.null
52 , Network.BitTorrent.Exchange.Assembler.size
53
54 -- * Construction
55 , Network.BitTorrent.Exchange.Assembler.empty
56 , Network.BitTorrent.Exchange.Assembler.allowPiece
57
58 -- * Debugging
59 , Network.BitTorrent.Exchange.Assembler.valid
3 ) where 60 ) where
4 61
5import Control.Applicative 62import Control.Applicative
63import Control.Lens
6import Data.IntMap.Strict as IM 64import Data.IntMap.Strict as IM
7import Data.List as L 65import Data.List as L
66import Data.Map as M
8import Data.Maybe 67import Data.Maybe
9 68
10import Data.Torrent.Piece 69import Data.Torrent.Piece
11import Network.BitTorrent.Exchange.Block 70import Network.BitTorrent.Core
71import Network.BitTorrent.Exchange.Block as B
12 72
73{-----------------------------------------------------------------------
74-- Assembler
75-----------------------------------------------------------------------}
13 76
77type BlockRange = (BlockOffset, BlockSize)
14type PieceMap = IntMap 78type PieceMap = IntMap
15 79
16data Assembler a = Assembler 80data Assembler = Assembler
17 { inflightSet :: PieceMap [BlockIx] 81 { -- | A set of blocks that have been 'Request'ed but not yet acked.
18 , piecePending :: PieceMap [Block a] 82 _inflight :: Map PeerAddr (PieceMap [BlockRange])
19 , pieceInfo :: PieceInfo 83
84 -- | A set of blocks that but not yet assembled.
85 , _pending :: PieceMap Bucket
86
87 -- | Used for validation of assembled pieces.
88 , info :: PieceInfo
20 } 89 }
21 90
91$(makeLenses ''Assembler)
92
93
94valid :: Assembler -> Bool
95valid = undefined
96
22data Result a 97data Result a
23 = Assembled (Piece a) 98 = Completed (Piece a)
24 | Corrupted PieceIx 99 | Corrupted PieceIx
25 | NotRequested PieceIx 100 | NotRequested PieceIx
26 | Overlapped BlockIx 101 | Overlapped BlockIx
27 102
28empty :: PieceInfo -> Assembler a 103null :: Assembler -> Bool
29empty = Assembler IM.empty IM.empty 104null = undefined
30
31inflightPieces :: Assembler a -> [PieceIx]
32inflightPieces Assembler {..} = keys piecePending
33 105
34completeBlocks :: PieceIx -> Assembler a -> [Block a] 106size :: Assembler -> Bool
35completeBlocks pix Assembler {..} = fromMaybe [] $ IM.lookup pix piecePending 107size = undefined
36
37incompleteBlocks :: PieceIx -> Assembler a -> [BlockIx]
38incompleteBlocks = undefined
39
40nextBlock :: Assembler a -> Maybe (Assembler a, BlockIx)
41nextBlock Assembler {..} = undefined
42 108
43allowPiece :: PieceIx -> Assembler a -> Assembler a 109empty :: PieceInfo -> Assembler
44allowPiece = undefined 110empty = Assembler M.empty IM.empty
45 111
46insert' :: Block a -> [Block a] -> [Block a] 112allowPiece :: PieceIx -> Assembler -> Assembler
47insert' a (x : xs) = undefined 113allowPiece pix a @ Assembler {..} = over pending (IM.insert pix bkt) a
114 where
115 bkt = B.empty (piPieceLength info)
48 116
49insertBlock :: Block a -> [Block a] -> Either [Block a] (Piece a) 117allowedSet :: PeerAddr -> Assembler -> [BlockIx]
50insertBlock = undefined 118allowedSet = undefined
51 119
52inserta :: Block a -> PieceMap [Block a] -> (PieceMap [Block a], Maybe (Piece a)) 120--inflight :: PeerAddr -> BlockIx -> Assembler -> Assembler
53inserta = undefined 121--inflight = undefined
54 122
55-- | You should check if a returned by peer block is actually have 123-- You should check if a returned by peer block is actually have
56-- been requested and in-flight. This is needed to avoid "I send 124-- been requested and in-flight. This is needed to avoid "I send
57-- random corrupted block" attacks. 125-- random corrupted block" attacks.
126insert :: PeerAddr -> Block a -> Assembler -> Assembler
127insert = undefined
128
129{-
58insert :: Block a -> Assembler a -> (Assembler a, Maybe (Result a)) 130insert :: Block a -> Assembler a -> (Assembler a, Maybe (Result a))
59insert blk @ Block {..} a @ Assembler {..} 131insert blk @ Block {..} a @ Assembler {..} = undefined
132{-
60 = let (pending, mpiece) = inserta blk piecePending 133 = let (pending, mpiece) = inserta blk piecePending
61 in (Assembler inflightSet pending pieceInfo, f <$> mpiece) 134 in (Assembler inflightSet pending pieceInfo, f <$> mpiece)
62 where 135 where
63 f p = undefined 136 f p = undefined
64-- | checkPieceLazy pieceInfo p = Assembled p 137-- | checkPieceLazy pieceInfo p = Assembled p
65-- | otherwise = Corrupted ixPiece 138-- | otherwise = Corrupted ixPiece
139-}
140
141
142inflightPieces :: Assembler a -> [PieceIx]
143inflightPieces Assembler {..} = IM.keys piecePending
144
145completeBlocks :: PieceIx -> Assembler a -> [Block a]
146completeBlocks pix Assembler {..} = fromMaybe [] $ IM.lookup pix piecePending
147
148incompleteBlocks :: PieceIx -> Assembler a -> [BlockIx]
149incompleteBlocks = undefined
150
151nextBlock :: Assembler a -> Maybe (Assembler a, BlockIx)
152nextBlock Assembler {..} = undefined
153
154inserta :: Block a
155 -> PieceMap [Block a]
156 -> (PieceMap [Block a], Maybe (Piece a))
157inserta = undefined
158
159-} \ No newline at end of file