summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
-rw-r--r--src/Data/Torrent/Block.hs11
-rw-r--r--src/Data/Torrent/Piece.hs7
2 files changed, 11 insertions, 7 deletions
diff --git a/src/Data/Torrent/Block.hs b/src/Data/Torrent/Block.hs
index 37889a7a..1e0a929d 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 #-}
13module Data.Torrent.Block 15module Data.Torrent.Block
14 ( -- * Piece attributes 16 ( -- * Piece attributes
15 PieceIx 17 PieceIx
@@ -38,6 +40,7 @@ import qualified Data.ByteString.Lazy as Lazy
38import Data.Char 40import Data.Char
39import Data.List as L 41import Data.List as L
40import Data.Serialize as S 42import Data.Serialize as S
43import Data.Typeable
41import Text.PrettyPrint 44import Text.PrettyPrint
42import Text.PrettyPrint.Class 45import 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 (L.map toLower . L.dropWhile isLower) ''BlockIx) 103$(deriveJSON (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.
154instance Pretty (Block Lazy.ByteString) where 157instance Pretty (Block Lazy.ByteString) where
diff --git a/src/Data/Torrent/Piece.hs b/src/Data/Torrent/Piece.hs
index 7eb4e3d5..c6223348 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 #-}
13module Data.Torrent.Piece 14module 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 (L.map toLower . L.dropWhile isLower) ''Piece) 121$(deriveJSON (L.map toLower . L.dropWhile isLower) ''Piece)
121 122