summaryrefslogtreecommitdiff
path: root/src/Data/Torrent/Block.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Torrent/Block.hs')
-rw-r--r--src/Data/Torrent/Block.hs27
1 files changed, 11 insertions, 16 deletions
diff --git a/src/Data/Torrent/Block.hs b/src/Data/Torrent/Block.hs
index cb50302c..987de653 100644
--- a/src/Data/Torrent/Block.hs
+++ b/src/Data/Torrent/Block.hs
@@ -9,6 +9,7 @@
9-- 9--
10{-# LANGUAGE GeneralizedNewtypeDeriving #-} 10{-# LANGUAGE GeneralizedNewtypeDeriving #-}
11{-# LANGUAGE TemplateHaskell #-} 11{-# LANGUAGE TemplateHaskell #-}
12{-# LANGUAGE FlexibleInstances #-}
12module Data.Torrent.Block 13module Data.Torrent.Block
13 ( -- * Piece attributes 14 ( -- * Piece attributes
14 PieceIx 15 PieceIx
@@ -22,31 +23,26 @@ module Data.Torrent.Block
22 23
23 -- * Block index 24 -- * Block index
24 , BlockIx(..) 25 , BlockIx(..)
25 , ppBlockIx
26 , blockIxRange 26 , blockIxRange
27 27
28 -- * Block data 28 -- * Block data
29 , Block(..) 29 , Block(..)
30 , ppBlock
31 , blockIx 30 , blockIx
32 , blockSize 31 , blockSize
33 , blockRange 32 , blockRange
34 ) where 33 ) where
35 34
36import Control.Applicative 35import Control.Applicative
37
38import Data.Aeson.TH 36import Data.Aeson.TH
39import qualified Data.ByteString.Lazy as Lazy 37import qualified Data.ByteString.Lazy as Lazy
40import Data.Char 38import Data.Char
41import Data.List as L 39import Data.List as L
42
43import Data.Binary as B 40import Data.Binary as B
44import Data.Binary.Get as B 41import Data.Binary.Get as B
45import Data.Binary.Put as B 42import Data.Binary.Put as B
46import Data.Serialize as S 43import Data.Serialize as S
47
48import Text.PrettyPrint 44import Text.PrettyPrint
49 45import Text.PrettyPrint.Class
50 46
51{----------------------------------------------------------------------- 47{-----------------------------------------------------------------------
52-- Piece attributes 48-- Piece attributes
@@ -147,12 +143,11 @@ instance Binary BlockIx where
147 putIntB ixOffset 143 putIntB ixOffset
148 putIntB ixLength 144 putIntB ixLength
149 145
150-- | Format block index in human readable form. 146instance Pretty BlockIx where
151ppBlockIx :: BlockIx -> Doc 147 pretty BlockIx {..} =
152ppBlockIx BlockIx {..} = 148 "piece = " <> int ixPiece <> "," <+>
153 "piece = " <> int ixPiece <> "," <+> 149 "offset = " <> int ixOffset <> "," <+>
154 "offset = " <> int ixOffset <> "," <+> 150 "length = " <> int ixLength
155 "length = " <> int ixLength
156 151
157-- | Get location of payload bytes in the torrent content. 152-- | Get location of payload bytes in the torrent content.
158blockIxRange :: (Num a, Integral a) => PieceSize -> BlockIx -> (a, a) 153blockIxRange :: (Num a, Integral a) => PieceSize -> BlockIx -> (a, a)
@@ -178,10 +173,10 @@ data Block payload = Block {
178 , blkData :: !payload 173 , blkData :: !payload
179 } deriving (Show, Eq) 174 } deriving (Show, Eq)
180 175
181-- | Format block in human readable form. Payload is ommitted. 176-- | Payload is ommitted.
182ppBlock :: Block Lazy.ByteString -> Doc 177instance Pretty (Block Lazy.ByteString) where
183ppBlock = ppBlockIx . blockIx 178 pretty = pretty . blockIx
184{-# INLINE ppBlock #-} 179 {-# INLINE pretty #-}
185 180
186-- | Get size of block /payload/ in bytes. 181-- | Get size of block /payload/ in bytes.
187blockSize :: Block Lazy.ByteString -> BlockSize 182blockSize :: Block Lazy.ByteString -> BlockSize