summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Network/BitTorrent/Exchange/Block.hs14
1 files changed, 7 insertions, 7 deletions
diff --git a/src/Network/BitTorrent/Exchange/Block.hs b/src/Network/BitTorrent/Exchange/Block.hs
index e99dd49d..ca635a75 100644
--- a/src/Network/BitTorrent/Exchange/Block.hs
+++ b/src/Network/BitTorrent/Exchange/Block.hs
@@ -33,7 +33,7 @@ module Network.BitTorrent.Exchange.Block
33 33
34import Control.Applicative 34import Control.Applicative
35import Data.Aeson.TH 35import Data.Aeson.TH
36import qualified Data.ByteString.Lazy as Lazy 36import Data.ByteString.Lazy as BL
37import Data.Char 37import Data.Char
38import Data.List as L 38import Data.List as L
39import Data.Serialize as S 39import Data.Serialize as S
@@ -138,26 +138,26 @@ data Block payload = Block {
138 } deriving (Show, Eq, Functor, Typeable) 138 } deriving (Show, Eq, Functor, Typeable)
139 139
140-- | Payload is ommitted. 140-- | Payload is ommitted.
141instance Pretty (Block Lazy.ByteString) where 141instance Pretty (Block BL.ByteString) where
142 pretty = pretty . blockIx 142 pretty = pretty . blockIx
143 {-# INLINE pretty #-} 143 {-# INLINE pretty #-}
144 144
145-- | Get size of block /payload/ in bytes. 145-- | Get size of block /payload/ in bytes.
146blockSize :: Block Lazy.ByteString -> BlockSize 146blockSize :: Block BL.ByteString -> BlockSize
147blockSize blk = fromIntegral (Lazy.length (blkData blk)) 147blockSize blk = fromIntegral (BL.length (blkData blk))
148{-# INLINE blockSize #-} 148{-# INLINE blockSize #-}
149 149
150-- | Get block index of a block. 150-- | Get block index of a block.
151blockIx :: Block Lazy.ByteString -> BlockIx 151blockIx :: Block BL.ByteString -> BlockIx
152blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize 152blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize
153 153
154-- | Get location of payload bytes in the torrent content. 154-- | Get location of payload bytes in the torrent content.
155blockRange :: (Num a, Integral a) => PieceSize -> Block Lazy.ByteString -> (a, a) 155blockRange :: (Num a, Integral a) => PieceSize -> Block BL.ByteString -> (a, a)
156blockRange pieceSize = blockIxRange pieceSize . blockIx 156blockRange pieceSize = blockIxRange pieceSize . blockIx
157{-# INLINE blockRange #-} 157{-# INLINE blockRange #-}
158 158
159-- | Test if a block can be safely turned into a piece. 159-- | Test if a block can be safely turned into a piece.
160isPiece :: PieceSize -> Block Lazy.ByteString -> Bool 160isPiece :: PieceSize -> Block BL.ByteString -> Bool
161isPiece pieceLen blk @ (Block i offset _) = 161isPiece pieceLen blk @ (Block i offset _) =
162 offset == 0 && blockSize blk == pieceLen && i >= 0 162 offset == 0 && blockSize blk == pieceLen && i >= 0
163{-# INLINE isPiece #-} 163{-# INLINE isPiece #-}