summaryrefslogtreecommitdiff
path: root/src/Data
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data')
-rw-r--r--src/Data/Torrent/Block.hs99
-rw-r--r--src/Data/Torrent/Piece.hs70
2 files changed, 88 insertions, 81 deletions
diff --git a/src/Data/Torrent/Block.hs b/src/Data/Torrent/Block.hs
index 17907a39..affbfa78 100644
--- a/src/Data/Torrent/Block.hs
+++ b/src/Data/Torrent/Block.hs
@@ -5,39 +5,39 @@
5-- Stability : experimental 5-- Stability : experimental
6-- Portability : portable 6-- Portability : portable
7-- 7--
8-- TODO 8-- Blocks are used to transfer pieces.
9-- 9--
10{-# LANGUAGE GeneralizedNewtypeDeriving #-} 10{-# LANGUAGE GeneralizedNewtypeDeriving #-}
11{-# LANGUAGE TemplateHaskell #-} 11{-# LANGUAGE TemplateHaskell #-}
12module Data.Torrent.Block 12module Data.Torrent.Block
13 ( -- * Block attributes 13 ( -- * Piece attributes
14 BlockLIx 14 PieceIx
15 , PieceLIx 15 , PieceSize
16
17 -- * Block attributes
18 , BlockOffset
19 , BlockCount
16 , BlockSize 20 , BlockSize
17 , defaultTransferSize 21 , defaultTransferSize
18 22
19 -- * Block index 23 -- * Block index
20 , BlockIx(..) 24 , BlockIx(..)
21 , ppBlockIx 25 , ppBlockIx
26 , blockIxRange
22 27
23 -- * Block data 28 -- * Block data
24 , Block(..) 29 , Block(..)
25 , ppBlock 30 , ppBlock
26 , blockSize
27 , pieceIx
28 , blockIx 31 , blockIx
32 , blockSize
29 , blockRange 33 , blockRange
30 , ixRange
31 , isPiece
32 ) where 34 ) where
33 35
34import Control.Applicative 36import Control.Applicative
35 37
36import Data.Aeson (ToJSON, FromJSON)
37import Data.Aeson.TH 38import Data.Aeson.TH
38import qualified Data.ByteString.Lazy as Lazy 39import qualified Data.ByteString.Lazy as Lazy
39import Data.Char 40import Data.Char
40import Data.Default
41import Data.List as L 41import Data.List as L
42 42
43import Data.Binary as B 43import Data.Binary as B
@@ -49,14 +49,37 @@ import Text.PrettyPrint
49 49
50 50
51{----------------------------------------------------------------------- 51{-----------------------------------------------------------------------
52-- Piece attributes
53-----------------------------------------------------------------------}
54
55-- | Zero-based index of piece in torrent content.
56type PieceIx = Int
57
58-- | Size of piece in bytes. Should be a power of 2.
59type PieceSize = Int
60
61{-----------------------------------------------------------------------
52-- Block attributes 62-- Block attributes
53-----------------------------------------------------------------------} 63-----------------------------------------------------------------------}
54 64
55type BlockSize = Int 65-- | Offset of a block in a piece in bytes. Should be multiple of
56type BlockLIx = Int 66-- the choosen block size.
57type PieceLIx = Int 67type BlockOffset = Int
68
69-- | Size of a block in bytes. Should be power of 2.
70--
71-- Normally block size is equal to 'defaultTransferSize'.
72--
73type BlockSize = Int
74
75-- | Number of block in a piece of a torrent. Used to distinguish
76-- block count from piece count.
77type BlockCount = Int
58 78
59-- | Widely used semi-official block size. 79-- | Widely used semi-official block size. Some clients can ignore if
80-- block size of BlockIx in Request message is not equal to this
81-- value.
82--
60defaultTransferSize :: BlockSize 83defaultTransferSize :: BlockSize
61defaultTransferSize = 16 * 1024 84defaultTransferSize = 16 * 1024
62 85
@@ -64,12 +87,13 @@ defaultTransferSize = 16 * 1024
64 Block Index 87 Block Index
65-----------------------------------------------------------------------} 88-----------------------------------------------------------------------}
66 89
90-- | BlockIx correspond.
67data BlockIx = BlockIx { 91data BlockIx = BlockIx {
68 -- | Zero-based piece index. 92 -- | Zero-based piece index.
69 ixPiece :: {-# UNPACK #-} !PieceLIx 93 ixPiece :: {-# UNPACK #-} !PieceIx
70 94
71 -- | Zero-based byte offset within the piece. 95 -- | Zero-based byte offset within the piece.
72 , ixOffset :: {-# UNPACK #-} !Int 96 , ixOffset :: {-# UNPACK #-} !BlockOffset
73 97
74 -- | Block size starting from offset. 98 -- | Block size starting from offset.
75 , ixLength :: {-# UNPACK #-} !BlockSize 99 , ixLength :: {-# UNPACK #-} !BlockSize
@@ -125,16 +149,25 @@ ppBlockIx BlockIx {..} =
125 "offset = " <> int ixOffset <> "," <+> 149 "offset = " <> int ixOffset <> "," <+>
126 "length = " <> int ixLength 150 "length = " <> int ixLength
127 151
152-- | Get location of payload bytes in the torrent content.
153blockIxRange :: (Num a, Integral a) => PieceSize -> BlockIx -> (a, a)
154blockIxRange pieceSize BlockIx {..} = (offset, offset + len)
155 where
156 offset = fromIntegral pieceSize * fromIntegral ixPiece
157 + fromIntegral ixOffset
158 len = fromIntegral ixLength
159{-# INLINE blockIxRange #-}
160
128{----------------------------------------------------------------------- 161{-----------------------------------------------------------------------
129 Block 162 Block
130-----------------------------------------------------------------------} 163-----------------------------------------------------------------------}
131 164
132data Block payload = Block { 165data Block payload = Block {
133 -- | Zero-based piece index. 166 -- | Zero-based piece index.
134 blkPiece :: {-# UNPACK #-} !PieceLIx 167 blkPiece :: {-# UNPACK #-} !PieceIx
135 168
136 -- | Zero-based byte offset within the piece. 169 -- | Zero-based byte offset within the piece.
137 , blkOffset :: {-# UNPACK #-} !Int 170 , blkOffset :: {-# UNPACK #-} !BlockOffset
138 171
139 -- | Payload bytes. 172 -- | Payload bytes.
140 , blkData :: !payload 173 , blkData :: !payload
@@ -145,36 +178,16 @@ ppBlock :: Block Lazy.ByteString -> Doc
145ppBlock = ppBlockIx . blockIx 178ppBlock = ppBlockIx . blockIx
146{-# INLINE ppBlock #-} 179{-# INLINE ppBlock #-}
147 180
181-- | Get size of block /payload/ in bytes.
148blockSize :: Block Lazy.ByteString -> BlockSize 182blockSize :: Block Lazy.ByteString -> BlockSize
149blockSize blk = fromIntegral (Lazy.length (blkData blk)) 183blockSize blk = fromIntegral (Lazy.length (blkData blk))
150{-# INLINE blockSize #-} 184{-# INLINE blockSize #-}
151 185
152isPiece :: Int -> Block Lazy.ByteString -> Bool 186-- | Get block index of a block.
153isPiece pieceSize (Block i offset bs) =
154 offset == 0
155 && fromIntegral (Lazy.length bs) == pieceSize
156 && i >= 0
157{-# INLINE isPiece #-}
158
159pieceIx :: Int -> Int -> BlockIx
160pieceIx i = BlockIx i 0
161{-# INLINE pieceIx #-}
162
163blockIx :: Block Lazy.ByteString -> BlockIx 187blockIx :: Block Lazy.ByteString -> BlockIx
164blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize 188blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize
165 189
166blockRange :: (Num a, Integral a) => Int -> Block Lazy.ByteString -> (a, a) 190-- | Get location of payload bytes in the torrent content.
167blockRange pieceSize blk = (offset, offset + len) 191blockRange :: (Num a, Integral a) => PieceSize -> Block Lazy.ByteString -> (a, a)
168 where 192blockRange pieceSize = blockIxRange pieceSize . blockIx
169 offset = fromIntegral pieceSize * fromIntegral (blkPiece blk)
170 + fromIntegral (blkOffset blk)
171 len = fromIntegral (Lazy.length (blkData blk))
172{-# INLINE blockRange #-} 193{-# INLINE blockRange #-}
173
174ixRange :: (Num a, Integral a) => Int -> BlockIx -> (a, a)
175ixRange pieceSize i = (offset, offset + len)
176 where
177 offset = fromIntegral pieceSize * fromIntegral (ixPiece i)
178 + fromIntegral (ixOffset i)
179 len = fromIntegral (ixLength i)
180{-# INLINE ixRange #-}
diff --git a/src/Data/Torrent/Piece.hs b/src/Data/Torrent/Piece.hs
index 27bc4879..572b136f 100644
--- a/src/Data/Torrent/Piece.hs
+++ b/src/Data/Torrent/Piece.hs
@@ -5,7 +5,7 @@
5-- Stability : experimental 5-- Stability : experimental
6-- Portability : portable 6-- Portability : portable
7-- 7--
8-- Torrent content validation. 8-- Pieces are used to validate torrent content.
9-- 9--
10{-# LANGUAGE TemplateHaskell #-} 10{-# LANGUAGE TemplateHaskell #-}
11{-# LANGUAGE DeriveDataTypeable #-} 11{-# LANGUAGE DeriveDataTypeable #-}
@@ -14,12 +14,16 @@ module Data.Torrent.Piece
14 ( -- * Piece attributes 14 ( -- * Piece attributes
15 PieceIx 15 PieceIx
16 , PieceCount 16 , PieceCount
17 , PieceSize (..) 17 , PieceSize
18 , defaultPieceSize 18 , defaultPieceSize
19 , maxPieceSize
20 , minPieceSize
19 21
20 -- * Piece data 22 -- * Piece data
21 , Piece (..) 23 , Piece (..)
22 , ppPiece 24 , ppPiece
25 , pieceSize
26 , isPiece
23 27
24 -- * Piece control 28 -- * Piece control
25 , PieceInfo (..) 29 , PieceInfo (..)
@@ -48,7 +52,6 @@ import Data.ByteString as BS
48import qualified Data.ByteString.Lazy as BL 52import qualified Data.ByteString.Lazy as BL
49import qualified Data.ByteString.Base64 as Base64 53import qualified Data.ByteString.Base64 as Base64
50import Data.Char 54import Data.Char
51import Data.Default
52import Data.Int 55import Data.Int
53import Data.List as L 56import Data.List as L
54import Data.Text.Encoding as T 57import Data.Text.Encoding as T
@@ -61,25 +64,18 @@ import Data.Torrent.Block
61class Lint a where 64class Lint a where
62 lint :: a -> Either String a 65 lint :: a -> Either String a
63 66
64type PieceIx = Int -- TODO remove 67-- | Number of pieces in torrent or a part of torrent.
68type PieceCount = Int
65 69
66newtype PieceCount = PieceCount { unPieceCount :: Int } 70-- | Optimal number of pieces in torrent.
67 71optimalPieceCount :: PieceCount
68-- | TODO 72optimalPieceCount = 1000
69instance Default PieceCount where 73{-# INLINE optimalPieceCount #-}
70 def = PieceCount 1000
71 {-# INLINE def #-}
72
73newtype PieceIndex = PieceIndex Int
74
75-- | An int used to denote piece size.
76newtype PieceSize = PieceSize Int
77 deriving (Show, Read, Typeable
78 , Eq, Ord, Enum
79 , Num, Real, Integral
80 , BEncode, ToJSON, FromJSON
81 )
82 74
75-- | NOTE: Have max and min size constrained to wide used
76-- semi-standard values. This bounds should be used to make decision
77-- about piece size for new torrents.
78--
83maxPieceSize :: Int 79maxPieceSize :: Int
84maxPieceSize = 4 * 1024 * 1024 80maxPieceSize = 4 * 1024 * 1024
85{-# INLINE maxPieceSize #-} 81{-# INLINE maxPieceSize #-}
@@ -88,18 +84,6 @@ minPieceSize :: Int
88minPieceSize = defaultTransferSize * 4 84minPieceSize = defaultTransferSize * 4
89{-# INLINE minPieceSize #-} 85{-# INLINE minPieceSize #-}
90 86
91-- | NOTE: Have max and min size constrained to wide used
92-- semi-standard values. This bounds should be used to make decision
93-- about piece size for new torrents.
94--
95instance Bounded PieceSize where
96 maxBound = PieceSize maxPieceSize
97 {-# INLINE maxBound #-}
98
99 minBound = PieceSize minPieceSize
100 {-# INLINE minBound #-}
101
102
103toPow2 :: Int -> Int 87toPow2 :: Int -> Int
104toPow2 x = bit $ fromIntegral (leadingZeros (0 :: Int) - leadingZeros x) 88toPow2 x = bit $ fromIntegral (leadingZeros (0 :: Int) - leadingZeros x)
105 89
@@ -107,13 +91,14 @@ toPow2 x = bit $ fromIntegral (leadingZeros (0 :: Int) - leadingZeros x)
107defaultPieceSize :: Int64 -> Int 91defaultPieceSize :: Int64 -> Int
108defaultPieceSize x = max minPieceSize $ min maxPieceSize $ toPow2 pc 92defaultPieceSize x = max minPieceSize $ min maxPieceSize $ toPow2 pc
109 where 93 where
110 pc = fromIntegral (x `div` fromIntegral (unPieceCount def)) 94 pc = fromIntegral (x `div` fromIntegral optimalPieceCount)
111 95
112-- TODO check if pieceLength is power of 2 96-- TODO check if pieceLength is power of 2
113-- | Piece payload should be strict or lazy bytestring. 97-- | Piece payload should be strict or lazy bytestring.
114data Piece a = Piece 98data Piece a = Piece
115 { -- | Zero-based piece index in torrent. TODO how pieces are indexed? 99 { -- | Zero-based piece index in torrent.
116 pieceIndex :: {-# UNPACK #-} !PieceIx 100 pieceIndex :: {-# UNPACK #-} !PieceIx
101
117 -- | Payload. 102 -- | Payload.
118 , pieceData :: !a 103 , pieceData :: !a
119 } deriving (Show, Read, Eq, Typeable) 104 } deriving (Show, Read, Eq, Typeable)
@@ -127,6 +112,16 @@ ppPiece :: Piece a -> Doc
127ppPiece Piece {..} 112ppPiece Piece {..}
128 = "Piece" <+> braces ("index" <+> "=" <+> int pieceIndex) 113 = "Piece" <+> braces ("index" <+> "=" <+> int pieceIndex)
129 114
115-- | Get size of piece in bytes.
116pieceSize :: Piece BL.ByteString -> PieceSize
117pieceSize Piece {..} = fromIntegral (BL.length pieceData)
118
119-- | Test if a block can be safely turned into a piece.
120isPiece :: PieceSize -> Block BL.ByteString -> Bool
121isPiece pieceSize blk @ (Block i offset _) =
122 offset == 0 && blockSize blk == pieceSize && i >= 0
123{-# INLINE isPiece #-}
124
130newtype HashArray = HashArray { unHashArray :: ByteString } 125newtype HashArray = HashArray { unHashArray :: ByteString }
131 deriving (Show, Read, Eq, BEncode) 126 deriving (Show, Read, Eq, BEncode)
132 127
@@ -181,7 +176,7 @@ instance BEncode PieceInfo where
181 176
182-- | Format piece info in human readable form. Hashes are omitted. 177-- | Format piece info in human readable form. Hashes are omitted.
183ppPieceInfo :: PieceInfo -> Doc 178ppPieceInfo :: PieceInfo -> Doc
184ppPieceInfo PieceInfo { piPieceLength = PieceSize len } = 179ppPieceInfo PieceInfo { piPieceLength = len } =
185 "PieceInfo" <+> braces ("length" <+> "=" <+> int len) 180 "PieceInfo" <+> braces ("length" <+> "=" <+> int len)
186 181
187hashsize :: Int 182hashsize :: Int
@@ -199,11 +194,10 @@ pieceHash PieceInfo {..} i = slice (hashsize * i) hashsize (unHashArray piPieceH
199-- | Find count of pieces in the torrent. If torrent size is not a 194-- | Find count of pieces in the torrent. If torrent size is not a
200-- multiple of piece size then the count is rounded up. 195-- multiple of piece size then the count is rounded up.
201pieceCount :: PieceInfo -> PieceCount 196pieceCount :: PieceInfo -> PieceCount
202pieceCount PieceInfo {..} 197pieceCount PieceInfo {..} = BS.length (unHashArray piPieceHashes) `quot` hashsize
203 = PieceCount (BS.length (unHashArray piPieceHashes) `quot` hashsize)
204 198
205isLastPiece :: PieceInfo -> PieceIx -> Bool 199isLastPiece :: PieceInfo -> PieceIx -> Bool
206isLastPiece ci i = unPieceCount (pieceCount ci) == succ i 200isLastPiece ci i = pieceCount ci == succ i
207 201
208class Validation a where 202class Validation a where
209 validate :: PieceInfo -> Piece a -> Bool 203 validate :: PieceInfo -> Piece a -> Bool