summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Data/Torrent/Block.hs153
1 files changed, 153 insertions, 0 deletions
diff --git a/src/Data/Torrent/Block.hs b/src/Data/Torrent/Block.hs
new file mode 100644
index 00000000..8aba4a6e
--- /dev/null
+++ b/src/Data/Torrent/Block.hs
@@ -0,0 +1,153 @@
1{-# LANGUAGE TemplateHaskell #-}
2module Data.Torrent.Block
3 ( -- * Block attribytes
4 BlockLIx
5 , PieceLIx
6
7 -- * Block index
8 , BlockIx(..)
9 , ppBlockIx
10
11 -- * Block data
12 , Block(..)
13 , ppBlock
14 , blockSize
15 , pieceIx
16 , blockIx
17 , blockRange
18 , ixRange
19 , isPiece
20 ) where
21
22import Control.Applicative
23
24import Data.Aeson.TH
25import qualified Data.ByteString.Lazy as Lazy
26import Data.Char
27import Data.List as L
28
29import Data.Binary as B
30import Data.Binary.Get as B
31import Data.Binary.Put as B
32import Data.Serialize as S
33
34import Text.PrettyPrint
35
36{-----------------------------------------------------------------------
37 Block Index
38-----------------------------------------------------------------------}
39
40type BlockLIx = Int
41type PieceLIx = Int
42
43
44data BlockIx = BlockIx {
45 -- | Zero-based piece index.
46 ixPiece :: {-# UNPACK #-} !PieceLIx
47
48 -- | Zero-based byte offset within the piece.
49 , ixOffset :: {-# UNPACK #-} !Int
50
51 -- | Block size starting from offset.
52 , ixLength :: {-# UNPACK #-} !Int
53 } deriving (Show, Eq)
54
55$(deriveJSON (L.map toLower . L.dropWhile isLower) ''BlockIx)
56
57getInt :: S.Get Int
58getInt = fromIntegral <$> S.getWord32be
59{-# INLINE getInt #-}
60
61putInt :: S.Putter Int
62putInt = S.putWord32be . fromIntegral
63{-# INLINE putInt #-}
64
65getIntB :: B.Get Int
66getIntB = fromIntegral <$> B.getWord32be
67{-# INLINE getIntB #-}
68
69putIntB :: Int -> B.Put
70putIntB = B.putWord32be . fromIntegral
71{-# INLINE putIntB #-}
72
73instance Serialize BlockIx where
74 {-# SPECIALIZE instance Serialize BlockIx #-}
75 get = BlockIx <$> getInt <*> getInt <*> getInt
76 {-# INLINE get #-}
77
78 put BlockIx {..} = do
79 putInt ixPiece
80 putInt ixOffset
81 putInt ixLength
82 {-# INLINE put #-}
83
84instance Binary BlockIx where
85 {-# SPECIALIZE instance Binary BlockIx #-}
86 get = BlockIx <$> getIntB <*> getIntB <*> getIntB
87 {-# INLINE get #-}
88
89 put BlockIx {..} = do
90 putIntB ixPiece
91 putIntB ixOffset
92 putIntB ixLength
93
94-- | Format block index in human readable form.
95ppBlockIx :: BlockIx -> Doc
96ppBlockIx BlockIx {..} =
97 "piece = " <> int ixPiece <> "," <+>
98 "offset = " <> int ixOffset <> "," <+>
99 "length = " <> int ixLength
100
101{-----------------------------------------------------------------------
102 Block
103-----------------------------------------------------------------------}
104
105data Block payload = Block {
106 -- | Zero-based piece index.
107 blkPiece :: {-# UNPACK #-} !PieceLIx
108
109 -- | Zero-based byte offset within the piece.
110 , blkOffset :: {-# UNPACK #-} !Int
111
112 -- | Payload bytes.
113 , blkData :: !payload
114 } deriving (Show, Eq)
115
116-- | Format block in human readable form. Payload is ommitted.
117ppBlock :: Block Lazy.ByteString -> Doc
118ppBlock = ppBlockIx . blockIx
119{-# INLINE ppBlock #-}
120
121blockSize :: Block Lazy.ByteString -> Int
122blockSize blk = fromIntegral (Lazy.length (blkData blk))
123{-# INLINE blockSize #-}
124
125isPiece :: Int -> Block Lazy.ByteString -> Bool
126isPiece pieceSize (Block i offset bs) =
127 offset == 0
128 && fromIntegral (Lazy.length bs) == pieceSize
129 && i >= 0
130{-# INLINE isPiece #-}
131
132pieceIx :: Int -> Int -> BlockIx
133pieceIx i = BlockIx i 0
134{-# INLINE pieceIx #-}
135
136blockIx :: Block Lazy.ByteString -> BlockIx
137blockIx = BlockIx <$> blkPiece <*> blkOffset <*> blockSize
138
139blockRange :: (Num a, Integral a) => Int -> Block Lazy.ByteString -> (a, a)
140blockRange pieceSize blk = (offset, offset + len)
141 where
142 offset = fromIntegral pieceSize * fromIntegral (blkPiece blk)
143 + fromIntegral (blkOffset blk)
144 len = fromIntegral (Lazy.length (blkData blk))
145{-# INLINE blockRange #-}
146
147ixRange :: (Num a, Integral a) => Int -> BlockIx -> (a, a)
148ixRange pieceSize i = (offset, offset + len)
149 where
150 offset = fromIntegral pieceSize * fromIntegral (ixPiece i)
151 + fromIntegral (ixOffset i)
152 len = fromIntegral (ixLength i)
153{-# INLINE ixRange #-}