diff options
Diffstat (limited to 'src/Network/BitTorrent/Exchange')
-rw-r--r-- | src/Network/BitTorrent/Exchange/Block.hs | 163 | ||||
-rw-r--r-- | src/Network/BitTorrent/Exchange/Message.hs | 2 |
2 files changed, 164 insertions, 1 deletions
diff --git a/src/Network/BitTorrent/Exchange/Block.hs b/src/Network/BitTorrent/Exchange/Block.hs new file mode 100644 index 00000000..e99dd49d --- /dev/null +++ b/src/Network/BitTorrent/Exchange/Block.hs | |||
@@ -0,0 +1,163 @@ | |||
1 | -- | | ||
2 | -- Copyright : (c) Sam Truzjan 2013 | ||
3 | -- License : BSD3 | ||
4 | -- Maintainer : pxqr.sta@gmail.com | ||
5 | -- Stability : experimental | ||
6 | -- Portability : portable | ||
7 | -- | ||
8 | -- Blocks are used to transfer pieces. | ||
9 | -- | ||
10 | {-# LANGUAGE FlexibleInstances #-} | ||
11 | {-# LANGUAGE TemplateHaskell #-} | ||
12 | {-# LANGUAGE DeriveFunctor #-} | ||
13 | {-# LANGUAGE DeriveDataTypeable #-} | ||
14 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
15 | module Network.BitTorrent.Exchange.Block | ||
16 | ( -- * Block attributes | ||
17 | BlockOffset | ||
18 | , BlockCount | ||
19 | , BlockSize | ||
20 | , defaultTransferSize | ||
21 | |||
22 | -- * Block index | ||
23 | , BlockIx(..) | ||
24 | , blockIxRange | ||
25 | |||
26 | -- * Block data | ||
27 | , Block(..) | ||
28 | , blockIx | ||
29 | , blockSize | ||
30 | , blockRange | ||
31 | , isPiece | ||
32 | ) where | ||
33 | |||
34 | import Control.Applicative | ||
35 | import Data.Aeson.TH | ||
36 | import qualified Data.ByteString.Lazy as Lazy | ||
37 | import Data.Char | ||
38 | import Data.List as L | ||
39 | import Data.Serialize as S | ||
40 | import Data.Typeable | ||
41 | import Text.PrettyPrint | ||
42 | import Text.PrettyPrint.Class | ||
43 | |||
44 | import Data.Torrent.Piece | ||
45 | |||
46 | {----------------------------------------------------------------------- | ||
47 | -- Block attributes | ||
48 | -----------------------------------------------------------------------} | ||
49 | |||
50 | -- | Offset of a block in a piece in bytes. Should be multiple of | ||
51 | -- the choosen block size. | ||
52 | type BlockOffset = Int | ||
53 | |||
54 | -- | Size of a block in bytes. Should be power of 2. | ||
55 | -- | ||
56 | -- Normally block size is equal to 'defaultTransferSize'. | ||
57 | -- | ||
58 | type BlockSize = Int | ||
59 | |||
60 | -- | Number of block in a piece of a torrent. Used to distinguish | ||
61 | -- block count from piece count. | ||
62 | type BlockCount = Int | ||
63 | |||
64 | -- | Widely used semi-official block size. Some clients can ignore if | ||
65 | -- block size of BlockIx in Request message is not equal to this | ||
66 | -- value. | ||
67 | -- | ||
68 | defaultTransferSize :: BlockSize | ||
69 | defaultTransferSize = 16 * 1024 | ||
70 | |||
71 | {----------------------------------------------------------------------- | ||
72 | Block Index | ||
73 | -----------------------------------------------------------------------} | ||
74 | |||
75 | -- | BlockIx correspond. | ||
76 | data BlockIx = BlockIx { | ||
77 | -- | Zero-based piece index. | ||
78 | ixPiece :: {-# UNPACK #-} !PieceIx | ||
79 | |||
80 | -- | Zero-based byte offset within the piece. | ||
81 | , ixOffset :: {-# UNPACK #-} !BlockOffset | ||
82 | |||
83 | -- | Block size starting from offset. | ||
84 | , ixLength :: {-# UNPACK #-} !BlockSize | ||
85 | } deriving (Show, Eq, Typeable) | ||
86 | |||
87 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''BlockIx) | ||
88 | |||
89 | getInt :: S.Get Int | ||
90 | getInt = fromIntegral <$> S.getWord32be | ||
91 | {-# INLINE getInt #-} | ||
92 | |||
93 | putInt :: S.Putter Int | ||
94 | putInt = S.putWord32be . fromIntegral | ||
95 | {-# INLINE putInt #-} | ||
96 | |||
97 | instance Serialize BlockIx where | ||
98 | {-# SPECIALIZE instance Serialize BlockIx #-} | ||
99 | get = BlockIx <$> getInt | ||
100 | <*> getInt | ||
101 | <*> getInt | ||
102 | {-# INLINE get #-} | ||
103 | |||
104 | put BlockIx {..} = do | ||
105 | putInt ixPiece | ||
106 | putInt ixOffset | ||
107 | putInt ixLength | ||
108 | {-# INLINE put #-} | ||
109 | |||
110 | instance Pretty BlockIx where | ||
111 | pretty BlockIx {..} = | ||
112 | "piece = " <> int ixPiece <> "," <+> | ||
113 | "offset = " <> int ixOffset <> "," <+> | ||
114 | "length = " <> int ixLength | ||
115 | |||
116 | -- | Get location of payload bytes in the torrent content. | ||
117 | blockIxRange :: (Num a, Integral a) => PieceSize -> BlockIx -> (a, a) | ||
118 | blockIxRange pieceSize BlockIx {..} = (offset, offset + len) | ||
119 | where | ||
120 | offset = fromIntegral pieceSize * fromIntegral ixPiece | ||
121 | + fromIntegral ixOffset | ||
122 | len = fromIntegral ixLength | ||
123 | {-# INLINE blockIxRange #-} | ||
124 | |||
125 | {----------------------------------------------------------------------- | ||
126 | Block | ||
127 | -----------------------------------------------------------------------} | ||
128 | |||
129 | data Block payload = Block { | ||
130 | -- | Zero-based piece index. | ||
131 | blkPiece :: {-# UNPACK #-} !PieceIx | ||
132 | |||
133 | -- | Zero-based byte offset within the piece. | ||
134 | , blkOffset :: {-# UNPACK #-} !BlockOffset | ||
135 | |||
136 | -- | Payload bytes. | ||
137 | , blkData :: !payload | ||
138 | } deriving (Show, Eq, Functor, Typeable) | ||
139 | |||
140 | -- | Payload is ommitted. | ||
141 | instance Pretty (Block Lazy.ByteString) where | ||
142 | pretty = pretty . blockIx | ||
143 | {-# INLINE pretty #-} | ||
144 | |||
145 | -- | Get size of block /payload/ in bytes. | ||
146 | blockSize :: Block Lazy.ByteString -> BlockSize | ||
147 | blockSize blk = fromIntegral (Lazy.length (blkData blk)) | ||
148 | {-# INLINE blockSize #-} | ||
149 | |||
150 | -- | Get block index of a block. | ||
151 | blockIx :: Block Lazy.ByteString -> BlockIx | ||
152 | blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize | ||
153 | |||
154 | -- | Get location of payload bytes in the torrent content. | ||
155 | blockRange :: (Num a, Integral a) => PieceSize -> Block Lazy.ByteString -> (a, a) | ||
156 | blockRange pieceSize = blockIxRange pieceSize . blockIx | ||
157 | {-# INLINE blockRange #-} | ||
158 | |||
159 | -- | Test if a block can be safely turned into a piece. | ||
160 | isPiece :: PieceSize -> Block Lazy.ByteString -> Bool | ||
161 | isPiece pieceLen blk @ (Block i offset _) = | ||
162 | offset == 0 && blockSize blk == pieceLen && i >= 0 | ||
163 | {-# INLINE isPiece #-} | ||
diff --git a/src/Network/BitTorrent/Exchange/Message.hs b/src/Network/BitTorrent/Exchange/Message.hs index 2f85d729..8a88b761 100644 --- a/src/Network/BitTorrent/Exchange/Message.hs +++ b/src/Network/BitTorrent/Exchange/Message.hs | |||
@@ -90,10 +90,10 @@ import Text.PrettyPrint as PP | |||
90 | import Text.PrettyPrint.Class | 90 | import Text.PrettyPrint.Class |
91 | 91 | ||
92 | import Data.Torrent.Bitfield | 92 | import Data.Torrent.Bitfield |
93 | import Data.Torrent.Block | ||
94 | import Data.Torrent.InfoHash | 93 | import Data.Torrent.InfoHash |
95 | import Network.BitTorrent.Core.PeerId | 94 | import Network.BitTorrent.Core.PeerId |
96 | import Network.BitTorrent.Core.PeerAddr () | 95 | import Network.BitTorrent.Core.PeerAddr () |
96 | import Network.BitTorrent.Exchange.Block | ||
97 | 97 | ||
98 | {----------------------------------------------------------------------- | 98 | {----------------------------------------------------------------------- |
99 | -- Extensions | 99 | -- Extensions |