diff options
Diffstat (limited to 'src/Data/Torrent')
-rw-r--r-- | src/Data/Torrent/Block.hs | 11 | ||||
-rw-r--r-- | src/Data/Torrent/Layout.hs | 14 | ||||
-rw-r--r-- | src/Data/Torrent/Piece.hs | 7 |
3 files changed, 18 insertions, 14 deletions
diff --git a/src/Data/Torrent/Block.hs b/src/Data/Torrent/Block.hs index fd12b7a0..089217fa 100644 --- a/src/Data/Torrent/Block.hs +++ b/src/Data/Torrent/Block.hs | |||
@@ -7,9 +7,11 @@ | |||
7 | -- | 7 | -- |
8 | -- Blocks are used to transfer pieces. | 8 | -- Blocks are used to transfer pieces. |
9 | -- | 9 | -- |
10 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
11 | {-# LANGUAGE TemplateHaskell #-} | ||
12 | {-# LANGUAGE FlexibleInstances #-} | 10 | {-# LANGUAGE FlexibleInstances #-} |
11 | {-# LANGUAGE TemplateHaskell #-} | ||
12 | {-# LANGUAGE DeriveFunctor #-} | ||
13 | {-# LANGUAGE DeriveDataTypeable #-} | ||
14 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | ||
13 | module Data.Torrent.Block | 15 | module Data.Torrent.Block |
14 | ( -- * Piece attributes | 16 | ( -- * Piece attributes |
15 | PieceIx | 17 | PieceIx |
@@ -38,6 +40,7 @@ import qualified Data.ByteString.Lazy as Lazy | |||
38 | import Data.Char | 40 | import Data.Char |
39 | import Data.List as L | 41 | import Data.List as L |
40 | import Data.Serialize as S | 42 | import Data.Serialize as S |
43 | import Data.Typeable | ||
41 | import Text.PrettyPrint | 44 | import Text.PrettyPrint |
42 | import Text.PrettyPrint.Class | 45 | import Text.PrettyPrint.Class |
43 | 46 | ||
@@ -95,7 +98,7 @@ data BlockIx = BlockIx { | |||
95 | 98 | ||
96 | -- | Block size starting from offset. | 99 | -- | Block size starting from offset. |
97 | , ixLength :: {-# UNPACK #-} !BlockSize | 100 | , ixLength :: {-# UNPACK #-} !BlockSize |
98 | } deriving (Show, Eq) | 101 | } deriving (Show, Eq, Typeable) |
99 | 102 | ||
100 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''BlockIx) | 103 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''BlockIx) |
101 | 104 | ||
@@ -148,7 +151,7 @@ data Block payload = Block { | |||
148 | 151 | ||
149 | -- | Payload bytes. | 152 | -- | Payload bytes. |
150 | , blkData :: !payload | 153 | , blkData :: !payload |
151 | } deriving (Show, Eq) | 154 | } deriving (Show, Eq, Functor, Typeable) |
152 | 155 | ||
153 | -- | Payload is ommitted. | 156 | -- | Payload is ommitted. |
154 | instance Pretty (Block Lazy.ByteString) where | 157 | instance Pretty (Block Lazy.ByteString) where |
diff --git a/src/Data/Torrent/Layout.hs b/src/Data/Torrent/Layout.hs index d39c6c04..c1e26d48 100644 --- a/src/Data/Torrent/Layout.hs +++ b/src/Data/Torrent/Layout.hs | |||
@@ -50,7 +50,7 @@ module Data.Torrent.Layout | |||
50 | , blockCount | 50 | , blockCount |
51 | 51 | ||
52 | -- * Flat file layout | 52 | -- * Flat file layout |
53 | , Layout | 53 | , FileLayout |
54 | , flatLayout | 54 | , flatLayout |
55 | , accumOffsets | 55 | , accumOffsets |
56 | , fileOffset | 56 | , fileOffset |
@@ -286,13 +286,13 @@ blockCount blkSize ci = contentLength ci `sizeInBase` blkSize | |||
286 | -- coalesce all the files in the given order to get the linear block | 286 | -- coalesce all the files in the given order to get the linear block |
287 | -- address space. | 287 | -- address space. |
288 | -- | 288 | -- |
289 | type Layout a = [(FilePath, a)] | 289 | type FileLayout a = [(FilePath, a)] |
290 | 290 | ||
291 | -- | Extract files layout from torrent info with the given root path. | 291 | -- | Extract files layout from torrent info with the given root path. |
292 | flatLayout | 292 | flatLayout |
293 | :: FilePath -- ^ Root path for the all torrent files. | 293 | :: FilePath -- ^ Root path for the all torrent files. |
294 | -> LayoutInfo -- ^ Torrent content information. | 294 | -> LayoutInfo -- ^ Torrent content information. |
295 | -> Layout FileSize -- ^ The all file paths prefixed with the given root. | 295 | -> FileLayout FileSize -- ^ The all file paths prefixed with the given root. |
296 | flatLayout prefixPath SingleFile { liFile = FileInfo {..} } | 296 | flatLayout prefixPath SingleFile { liFile = FileInfo {..} } |
297 | = [(prefixPath </> BC.unpack fiName, fiLength)] | 297 | = [(prefixPath </> BC.unpack fiName, fiLength)] |
298 | flatLayout prefixPath MultiFile {..} = L.map mkPath liFiles | 298 | flatLayout prefixPath MultiFile {..} = L.map mkPath liFiles |
@@ -303,14 +303,14 @@ flatLayout prefixPath MultiFile {..} = L.map mkPath liFiles | |||
303 | </> joinPath (L.map BC.unpack fiName) | 303 | </> joinPath (L.map BC.unpack fiName) |
304 | 304 | ||
305 | -- | Calculate offset of each file based on its length, incrementally. | 305 | -- | Calculate offset of each file based on its length, incrementally. |
306 | accumOffsets :: Layout FileSize -> Layout FileOffset | 306 | accumOffsets :: FileLayout FileSize -> FileLayout FileOffset |
307 | accumOffsets = go 0 | 307 | accumOffsets = go 0 |
308 | where | 308 | where |
309 | go !_ [] = [] | 309 | go !_ [] = [] |
310 | go !offset ((n, s) : xs) = (n, offset) : go (offset + s) xs | 310 | go !offset ((n, s) : xs) = (n, offset) : go (offset + s) xs |
311 | 311 | ||
312 | -- | Gives global offset of a content file for a given full path. | 312 | -- | Gives global offset of a content file for a given full path. |
313 | fileOffset :: FilePath -> Layout FileOffset -> Maybe FileOffset | 313 | fileOffset :: FilePath -> FileLayout FileOffset -> Maybe FileOffset |
314 | fileOffset = lookup | 314 | fileOffset = lookup |
315 | {-# INLINE fileOffset #-} | 315 | {-# INLINE fileOffset #-} |
316 | 316 | ||
diff --git a/src/Data/Torrent/Piece.hs b/src/Data/Torrent/Piece.hs index f7c6257b..31680ce8 100644 --- a/src/Data/Torrent/Piece.hs +++ b/src/Data/Torrent/Piece.hs | |||
@@ -7,8 +7,9 @@ | |||
7 | -- | 7 | -- |
8 | -- Pieces are used to validate torrent content. | 8 | -- Pieces are used to validate torrent content. |
9 | -- | 9 | -- |
10 | {-# LANGUAGE TemplateHaskell #-} | 10 | {-# LANGUAGE TemplateHaskell #-} |
11 | {-# LANGUAGE DeriveDataTypeable #-} | 11 | {-# LANGUAGE DeriveDataTypeable #-} |
12 | {-# LANGUAGE DeriveFunctor #-} | ||
12 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 13 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
13 | module Data.Torrent.Piece | 14 | module Data.Torrent.Piece |
14 | ( -- * Piece attributes | 15 | ( -- * Piece attributes |
@@ -115,7 +116,7 @@ data Piece a = Piece | |||
115 | 116 | ||
116 | -- | Payload. | 117 | -- | Payload. |
117 | , pieceData :: !a | 118 | , pieceData :: !a |
118 | } deriving (Show, Read, Eq, Typeable) | 119 | } deriving (Show, Read, Eq, Functor, Typeable) |
119 | 120 | ||
120 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''Piece) | 121 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''Piece) |
121 | 122 | ||