summaryrefslogtreecommitdiff
path: root/src/Network/BitTorrent/Exchange/Block.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Network/BitTorrent/Exchange/Block.hs')
-rw-r--r--src/Network/BitTorrent/Exchange/Block.hs11
1 files changed, 5 insertions, 6 deletions
diff --git a/src/Network/BitTorrent/Exchange/Block.hs b/src/Network/BitTorrent/Exchange/Block.hs
index 8e3ef91f..ca126acb 100644
--- a/src/Network/BitTorrent/Exchange/Block.hs
+++ b/src/Network/BitTorrent/Exchange/Block.hs
@@ -34,9 +34,7 @@ module Network.BitTorrent.Exchange.Block
34import Control.Applicative 34import Control.Applicative
35import Data.Aeson.TH 35import Data.Aeson.TH
36import Data.ByteString.Lazy as BL 36import Data.ByteString.Lazy as BL
37import Data.Char
38import Data.Default 37import Data.Default
39import Data.List as L
40import Data.Serialize as S 38import Data.Serialize as S
41import Data.Typeable 39import Data.Typeable
42import Text.PrettyPrint 40import Text.PrettyPrint
@@ -121,9 +119,9 @@ instance Pretty BlockIx where
121 119
122-- | Get location of payload bytes in the torrent content. 120-- | Get location of payload bytes in the torrent content.
123blockIxRange :: (Num a, Integral a) => PieceSize -> BlockIx -> (a, a) 121blockIxRange :: (Num a, Integral a) => PieceSize -> BlockIx -> (a, a)
124blockIxRange pieceSize BlockIx {..} = (offset, offset + len) 122blockIxRange piSize BlockIx {..} = (offset, offset + len)
125 where 123 where
126 offset = fromIntegral pieceSize * fromIntegral ixPiece 124 offset = fromIntegral piSize * fromIntegral ixPiece
127 + fromIntegral ixOffset 125 + fromIntegral ixOffset
128 len = fromIntegral ixLength 126 len = fromIntegral ixLength
129{-# INLINE blockIxRange #-} 127{-# INLINE blockIxRange #-}
@@ -158,8 +156,9 @@ blockIx :: Block BL.ByteString -> BlockIx
158blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize 156blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize
159 157
160-- | Get location of payload bytes in the torrent content. 158-- | Get location of payload bytes in the torrent content.
161blockRange :: (Num a, Integral a) => PieceSize -> Block BL.ByteString -> (a, a) 159blockRange :: (Num a, Integral a)
162blockRange pieceSize = blockIxRange pieceSize . blockIx 160 => PieceSize -> Block BL.ByteString -> (a, a)
161blockRange piSize = blockIxRange piSize . blockIx
163{-# INLINE blockRange #-} 162{-# INLINE blockRange #-}
164 163
165-- | Test if a block can be safely turned into a piece. 164-- | Test if a block can be safely turned into a piece.