summaryrefslogtreecommitdiff
path: root/src/Data/Torrent
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-12-05 03:40:11 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-12-05 03:40:11 +0400
commitaa86e6191cfdd0585808ae1f12355918996d3ee5 (patch)
tree94c22d905d28628a1b9de70f31ca0917e5cbf49c /src/Data/Torrent
parent32b0f3570237e4d4742fc8874980f2b479c1ae75 (diff)
Move piece attributes to the Piece module
Diffstat (limited to 'src/Data/Torrent')
-rw-r--r--src/Data/Torrent/Block.hs30
-rw-r--r--src/Data/Torrent/Piece.hs29
2 files changed, 27 insertions, 32 deletions
diff --git a/src/Data/Torrent/Block.hs b/src/Data/Torrent/Block.hs
index 089217fa..88f7f352 100644
--- a/src/Data/Torrent/Block.hs
+++ b/src/Data/Torrent/Block.hs
@@ -13,12 +13,8 @@
13{-# LANGUAGE DeriveDataTypeable #-} 13{-# LANGUAGE DeriveDataTypeable #-}
14{-# LANGUAGE GeneralizedNewtypeDeriving #-} 14{-# LANGUAGE GeneralizedNewtypeDeriving #-}
15module Data.Torrent.Block 15module Data.Torrent.Block
16 ( -- * Piece attributes 16 ( -- * Block attributes
17 PieceIx 17 BlockOffset
18 , PieceSize
19
20 -- * Block attributes
21 , BlockOffset
22 , BlockCount 18 , BlockCount
23 , BlockSize 19 , BlockSize
24 , defaultTransferSize 20 , defaultTransferSize
@@ -32,6 +28,7 @@ module Data.Torrent.Block
32 , blockIx 28 , blockIx
33 , blockSize 29 , blockSize
34 , blockRange 30 , blockRange
31 , isPiece
35 ) where 32 ) where
36 33
37import Control.Applicative 34import Control.Applicative
@@ -44,20 +41,7 @@ import Data.Typeable
44import Text.PrettyPrint 41import Text.PrettyPrint
45import Text.PrettyPrint.Class 42import Text.PrettyPrint.Class
46 43
47{----------------------------------------------------------------------- 44import Data.Torrent.Piece
48-- Piece attributes
49-----------------------------------------------------------------------}
50
51-- | Zero-based index of piece in torrent content.
52type PieceIx = Int
53
54-- | Size of piece in bytes. Should be a power of 2.
55--
56-- NOTE: Have max and min size constrained to wide used
57-- semi-standard values. This bounds should be used to make decision
58-- about piece size for new torrents.
59--
60type PieceSize = Int
61 45
62{----------------------------------------------------------------------- 46{-----------------------------------------------------------------------
63-- Block attributes 47-- Block attributes
@@ -171,3 +155,9 @@ blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize
171blockRange :: (Num a, Integral a) => PieceSize -> Block Lazy.ByteString -> (a, a) 155blockRange :: (Num a, Integral a) => PieceSize -> Block Lazy.ByteString -> (a, a)
172blockRange pieceSize = blockIxRange pieceSize . blockIx 156blockRange pieceSize = blockIxRange pieceSize . blockIx
173{-# INLINE blockRange #-} 157{-# INLINE blockRange #-}
158
159-- | Test if a block can be safely turned into a piece.
160isPiece :: PieceSize -> Block Lazy.ByteString -> Bool
161isPiece pieceLen blk @ (Block i offset _) =
162 offset == 0 && blockSize blk == pieceLen && i >= 0
163{-# INLINE isPiece #-}
diff --git a/src/Data/Torrent/Piece.hs b/src/Data/Torrent/Piece.hs
index 31680ce8..00d4b843 100644
--- a/src/Data/Torrent/Piece.hs
+++ b/src/Data/Torrent/Piece.hs
@@ -23,7 +23,6 @@ module Data.Torrent.Piece
23 -- * Piece data 23 -- * Piece data
24 , Piece (..) 24 , Piece (..)
25 , pieceSize 25 , pieceSize
26 , isPiece
27 26
28 -- * Piece control 27 -- * Piece control
29 , HashArray (..) 28 , HashArray (..)
@@ -63,11 +62,9 @@ import Data.Typeable
63import Text.PrettyPrint 62import Text.PrettyPrint
64import Text.PrettyPrint.Class 63import Text.PrettyPrint.Class
65 64
66import Data.Torrent.Block 65-- TODO add torrent file validation
67
68
69class Lint a where 66class Lint a where
70 lint :: a -> Either String a 67 lint :: a -> Either String a
71 68
72--class Validation a where 69--class Validation a where
73-- validate :: PieceInfo -> Piece a -> Bool 70-- validate :: PieceInfo -> Piece a -> Bool
@@ -76,9 +73,23 @@ class Lint a where
76-- Piece attributes 73-- Piece attributes
77-----------------------------------------------------------------------} 74-----------------------------------------------------------------------}
78 75
76-- | Zero-based index of piece in torrent content.
77type PieceIx = Int
78
79-- | Size of piece in bytes. Should be a power of 2.
80--
81-- NOTE: Have max and min size constrained to wide used
82-- semi-standard values. This bounds should be used to make decision
83-- about piece size for new torrents.
84--
85type PieceSize = Int
86
79-- | Number of pieces in torrent or a part of torrent. 87-- | Number of pieces in torrent or a part of torrent.
80type PieceCount = Int 88type PieceCount = Int
81 89
90defaultBlockSize :: Int
91defaultBlockSize = 16 * 1024
92
82-- | Optimal number of pieces in torrent. 93-- | Optimal number of pieces in torrent.
83optimalPieceCount :: PieceCount 94optimalPieceCount :: PieceCount
84optimalPieceCount = 1000 95optimalPieceCount = 1000
@@ -86,7 +97,7 @@ optimalPieceCount = 1000
86 97
87-- | Piece size should not be less than this value. 98-- | Piece size should not be less than this value.
88minPieceSize :: Int 99minPieceSize :: Int
89minPieceSize = defaultTransferSize * 4 100minPieceSize = defaultBlockSize * 4
90{-# INLINE minPieceSize #-} 101{-# INLINE minPieceSize #-}
91 102
92-- | To prevent transfer degradation piece size should not exceed this 103-- | To prevent transfer degradation piece size should not exceed this
@@ -130,12 +141,6 @@ instance Pretty (Piece a) where
130pieceSize :: Piece BL.ByteString -> PieceSize 141pieceSize :: Piece BL.ByteString -> PieceSize
131pieceSize Piece {..} = fromIntegral (BL.length pieceData) 142pieceSize Piece {..} = fromIntegral (BL.length pieceData)
132 143
133-- | Test if a block can be safely turned into a piece.
134isPiece :: PieceSize -> Block BL.ByteString -> Bool
135isPiece pieceLen blk @ (Block i offset _) =
136 offset == 0 && blockSize blk == pieceLen && i >= 0
137{-# INLINE isPiece #-}
138
139{----------------------------------------------------------------------- 144{-----------------------------------------------------------------------
140-- Piece control 145-- Piece control
141-----------------------------------------------------------------------} 146-----------------------------------------------------------------------}