diff options
Diffstat (limited to 'src')
-rw-r--r-- | src/Data/Torrent.hs | 8 | ||||
-rw-r--r-- | src/Data/Torrent/Block.hs | 2 | ||||
-rw-r--r-- | src/Data/Torrent/InfoHash.hs | 4 | ||||
-rw-r--r-- | src/Data/Torrent/Layout.hs | 4 | ||||
-rw-r--r-- | src/Data/Torrent/Piece.hs | 4 | ||||
-rw-r--r-- | src/Data/Torrent/Progress.hs | 2 | ||||
-rw-r--r-- | src/Network/BitTorrent/Core/PeerAddr.hs | 2 | ||||
-rw-r--r-- | src/Network/BitTorrent/Core/PeerId.hs | 4 | ||||
-rw-r--r-- | src/Network/BitTorrent/Exchange/Status.hs | 4 | ||||
-rw-r--r-- | src/Network/BitTorrent/Tracker/RPC/Message.hs | 8 |
10 files changed, 21 insertions, 21 deletions
diff --git a/src/Data/Torrent.hs b/src/Data/Torrent.hs index b3ac7586..ce919907 100644 --- a/src/Data/Torrent.hs +++ b/src/Data/Torrent.hs | |||
@@ -123,7 +123,7 @@ data InfoDict = InfoDict | |||
123 | -- BEP 27: <http://www.bittorrent.org/beps/bep_0027.html> | 123 | -- BEP 27: <http://www.bittorrent.org/beps/bep_0027.html> |
124 | } deriving (Show, Read, Eq, Typeable) | 124 | } deriving (Show, Read, Eq, Typeable) |
125 | 125 | ||
126 | $(deriveJSON (L.map Char.toLower . L.dropWhile isLower) ''InfoDict) | 126 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map Char.toLower . L.dropWhile isLower) } ''InfoDict) |
127 | 127 | ||
128 | makeLensesFor | 128 | makeLensesFor |
129 | [ ("idInfoHash" , "infohash" ) | 129 | [ ("idInfoHash" , "infohash" ) |
@@ -137,8 +137,8 @@ instance NFData InfoDict where | |||
137 | rnf InfoDict {..} = rnf idLayoutInfo | 137 | rnf InfoDict {..} = rnf idLayoutInfo |
138 | 138 | ||
139 | instance Hashable InfoDict where | 139 | instance Hashable InfoDict where |
140 | hash = Hashable.hash . idInfoHash | 140 | hashWithSalt = Hashable.hashUsing idInfoHash |
141 | {-# INLINE hash #-} | 141 | {-# INLINE hashWithSalt #-} |
142 | 142 | ||
143 | -- | Smart constructor: add a info hash to info dictionary. | 143 | -- | Smart constructor: add a info hash to info dictionary. |
144 | infoDictionary :: LayoutInfo -> PieceInfo -> Bool -> InfoDict | 144 | infoDictionary :: LayoutInfo -> PieceInfo -> Bool -> InfoDict |
@@ -239,7 +239,7 @@ instance ToJSON NominalDiffTime where | |||
239 | instance FromJSON NominalDiffTime where | 239 | instance FromJSON NominalDiffTime where |
240 | parseJSON v = utcTimeToPOSIXSeconds <$> parseJSON v | 240 | parseJSON v = utcTimeToPOSIXSeconds <$> parseJSON v |
241 | 241 | ||
242 | $(deriveJSON (L.map Char.toLower . L.dropWhile isLower) ''Torrent) | 242 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map Char.toLower . L.dropWhile isLower) } ''Torrent) |
243 | 243 | ||
244 | makeLensesFor | 244 | makeLensesFor |
245 | [ ("tAnnounce" , "announce" ) | 245 | [ ("tAnnounce" , "announce" ) |
diff --git a/src/Data/Torrent/Block.hs b/src/Data/Torrent/Block.hs index 1e0a929d..089217fa 100644 --- a/src/Data/Torrent/Block.hs +++ b/src/Data/Torrent/Block.hs | |||
@@ -100,7 +100,7 @@ data BlockIx = BlockIx { | |||
100 | , ixLength :: {-# UNPACK #-} !BlockSize | 100 | , ixLength :: {-# UNPACK #-} !BlockSize |
101 | } deriving (Show, Eq, Typeable) | 101 | } deriving (Show, Eq, Typeable) |
102 | 102 | ||
103 | $(deriveJSON (L.map toLower . L.dropWhile isLower) ''BlockIx) | 103 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''BlockIx) |
104 | 104 | ||
105 | getInt :: S.Get Int | 105 | getInt :: S.Get Int |
106 | getInt = fromIntegral <$> S.getWord32be | 106 | getInt = fromIntegral <$> S.getWord32be |
diff --git a/src/Data/Torrent/InfoHash.hs b/src/Data/Torrent/InfoHash.hs index d840ac87..4d49fcb7 100644 --- a/src/Data/Torrent/InfoHash.hs +++ b/src/Data/Torrent/InfoHash.hs | |||
@@ -70,8 +70,8 @@ instance Default InfoHash where | |||
70 | 70 | ||
71 | -- | Hash raw bytes. (no encoding) | 71 | -- | Hash raw bytes. (no encoding) |
72 | instance Hashable InfoHash where | 72 | instance Hashable InfoHash where |
73 | hash (InfoHash ih) = Hashable.hash ih | 73 | hashWithSalt s (InfoHash ih) = hashWithSalt s ih |
74 | {-# INLINE hash #-} | 74 | {-# INLINE hashWithSalt #-} |
75 | 75 | ||
76 | -- | Convert to\/from raw bencoded string. (no encoding) | 76 | -- | Convert to\/from raw bencoded string. (no encoding) |
77 | instance BEncode InfoHash where | 77 | instance BEncode InfoHash where |
diff --git a/src/Data/Torrent/Layout.hs b/src/Data/Torrent/Layout.hs index 54ec0f23..c1e26d48 100644 --- a/src/Data/Torrent/Layout.hs +++ b/src/Data/Torrent/Layout.hs | |||
@@ -125,7 +125,7 @@ data FileInfo a = FileInfo { | |||
125 | , Functor, Foldable | 125 | , Functor, Foldable |
126 | ) | 126 | ) |
127 | 127 | ||
128 | $(deriveJSON (L.map Char.toLower . L.dropWhile isLower) ''FileInfo) | 128 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map Char.toLower . L.dropWhile isLower) } ''FileInfo) |
129 | 129 | ||
130 | makeLensesFor | 130 | makeLensesFor |
131 | [ ("fiLength", "fileLength") | 131 | [ ("fiLength", "fileLength") |
@@ -210,7 +210,7 @@ data LayoutInfo | |||
210 | , liDirName :: !ByteString | 210 | , liDirName :: !ByteString |
211 | } deriving (Show, Read, Eq, Typeable) | 211 | } deriving (Show, Read, Eq, Typeable) |
212 | 212 | ||
213 | $(deriveJSON (L.map Char.toLower . L.dropWhile isLower) ''LayoutInfo) | 213 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map Char.toLower . L.dropWhile isLower) } ''LayoutInfo) |
214 | 214 | ||
215 | makeLensesFor | 215 | makeLensesFor |
216 | [ ("liFile" , "singleFile" ) | 216 | [ ("liFile" , "singleFile" ) |
diff --git a/src/Data/Torrent/Piece.hs b/src/Data/Torrent/Piece.hs index c6223348..31680ce8 100644 --- a/src/Data/Torrent/Piece.hs +++ b/src/Data/Torrent/Piece.hs | |||
@@ -118,7 +118,7 @@ data Piece a = Piece | |||
118 | , pieceData :: !a | 118 | , pieceData :: !a |
119 | } deriving (Show, Read, Eq, Functor, Typeable) | 119 | } deriving (Show, Read, Eq, Functor, Typeable) |
120 | 120 | ||
121 | $(deriveJSON (L.map toLower . L.dropWhile isLower) ''Piece) | 121 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''Piece) |
122 | 122 | ||
123 | instance NFData (Piece a) | 123 | instance NFData (Piece a) |
124 | 124 | ||
@@ -161,7 +161,7 @@ data PieceInfo = PieceInfo | |||
161 | -- ^ Concatenation of all 20-byte SHA1 hash values. | 161 | -- ^ Concatenation of all 20-byte SHA1 hash values. |
162 | } deriving (Show, Read, Eq, Typeable) | 162 | } deriving (Show, Read, Eq, Typeable) |
163 | 163 | ||
164 | $(deriveJSON (L.map toLower . L.dropWhile isLower) ''PieceInfo) | 164 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''PieceInfo) |
165 | 165 | ||
166 | -- | Number of bytes in each piece. | 166 | -- | Number of bytes in each piece. |
167 | makeLensesFor [("piPieceLength", "pieceLength")] ''PieceInfo | 167 | makeLensesFor [("piPieceLength", "pieceLength")] ''PieceInfo |
diff --git a/src/Data/Torrent/Progress.hs b/src/Data/Torrent/Progress.hs index 1a4a68e2..34f8f299 100644 --- a/src/Data/Torrent/Progress.hs +++ b/src/Data/Torrent/Progress.hs | |||
@@ -62,7 +62,7 @@ data Progress = Progress | |||
62 | } deriving (Show, Read, Eq) | 62 | } deriving (Show, Read, Eq) |
63 | 63 | ||
64 | $(makeLenses ''Progress) | 64 | $(makeLenses ''Progress) |
65 | $(deriveJSON L.tail ''Progress) | 65 | $(deriveJSON defaultOptions { fieldLabelModifier = L.tail } ''Progress) |
66 | 66 | ||
67 | -- | UDP tracker compatible encoding. | 67 | -- | UDP tracker compatible encoding. |
68 | instance Serialize Progress where | 68 | instance Serialize Progress where |
diff --git a/src/Network/BitTorrent/Core/PeerAddr.hs b/src/Network/BitTorrent/Core/PeerAddr.hs index e58aaa89..ed2dc672 100644 --- a/src/Network/BitTorrent/Core/PeerAddr.hs +++ b/src/Network/BitTorrent/Core/PeerAddr.hs | |||
@@ -62,7 +62,7 @@ data PeerAddr = PeerAddr { | |||
62 | , peerPort :: {-# UNPACK #-} !PortNumber | 62 | , peerPort :: {-# UNPACK #-} !PortNumber |
63 | } deriving (Show, Eq, Ord, Typeable) | 63 | } deriving (Show, Eq, Ord, Typeable) |
64 | 64 | ||
65 | $(deriveJSON (L.map toLower . L.dropWhile isLower) ''PeerAddr) | 65 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''PeerAddr) |
66 | 66 | ||
67 | -- | The tracker "announce query" compatible encoding. | 67 | -- | The tracker "announce query" compatible encoding. |
68 | instance BEncode PeerAddr where | 68 | instance BEncode PeerAddr where |
diff --git a/src/Network/BitTorrent/Core/PeerId.hs b/src/Network/BitTorrent/Core/PeerId.hs index 148f550d..1b4409a8 100644 --- a/src/Network/BitTorrent/Core/PeerId.hs +++ b/src/Network/BitTorrent/Core/PeerId.hs | |||
@@ -74,8 +74,8 @@ peerIdLen :: Int | |||
74 | peerIdLen = 20 | 74 | peerIdLen = 20 |
75 | 75 | ||
76 | instance Hashable PeerId where | 76 | instance Hashable PeerId where |
77 | hash = hash . getPeerId | 77 | hashWithSalt = hashUsing getPeerId |
78 | {-# INLINE hash #-} | 78 | {-# INLINE hashWithSalt #-} |
79 | 79 | ||
80 | instance Serialize PeerId where | 80 | instance Serialize PeerId where |
81 | put = putByteString . getPeerId | 81 | put = putByteString . getPeerId |
diff --git a/src/Network/BitTorrent/Exchange/Status.hs b/src/Network/BitTorrent/Exchange/Status.hs index 7920f2a1..ae323e09 100644 --- a/src/Network/BitTorrent/Exchange/Status.hs +++ b/src/Network/BitTorrent/Exchange/Status.hs | |||
@@ -35,7 +35,7 @@ data PeerStatus = PeerStatus { | |||
35 | } deriving (Show, Eq) | 35 | } deriving (Show, Eq) |
36 | 36 | ||
37 | $(makeLenses ''PeerStatus) | 37 | $(makeLenses ''PeerStatus) |
38 | $(deriveJSON L.tail ''PeerStatus) | 38 | $(deriveJSON defaultOptions { fieldLabelModifier = L.tail } ''PeerStatus) |
39 | 39 | ||
40 | instance Default PeerStatus where | 40 | instance Default PeerStatus where |
41 | def = PeerStatus True False | 41 | def = PeerStatus True False |
@@ -56,7 +56,7 @@ data SessionStatus = SessionStatus { | |||
56 | } deriving (Show, Eq) | 56 | } deriving (Show, Eq) |
57 | 57 | ||
58 | $(makeLenses ''SessionStatus) | 58 | $(makeLenses ''SessionStatus) |
59 | $(deriveJSON L.tail ''SessionStatus) | 59 | $(deriveJSON defaultOptions { fieldLabelModifier = L.tail } ''SessionStatus) |
60 | 60 | ||
61 | instance Default SessionStatus where | 61 | instance Default SessionStatus where |
62 | def = SessionStatus def def | 62 | def = SessionStatus def def |
diff --git a/src/Network/BitTorrent/Tracker/RPC/Message.hs b/src/Network/BitTorrent/Tracker/RPC/Message.hs index cefe96d5..3900ff64 100644 --- a/src/Network/BitTorrent/Tracker/RPC/Message.hs +++ b/src/Network/BitTorrent/Tracker/RPC/Message.hs | |||
@@ -104,7 +104,7 @@ data Event = Started | |||
104 | -- ^ To be sent when the peer completes a download. | 104 | -- ^ To be sent when the peer completes a download. |
105 | deriving (Show, Read, Eq, Ord, Enum, Bounded, Typeable) | 105 | deriving (Show, Read, Eq, Ord, Enum, Bounded, Typeable) |
106 | 106 | ||
107 | $(deriveJSON (L.map toLower . L.dropWhile isLower) ''Event) | 107 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''Event) |
108 | 108 | ||
109 | -- | HTTP tracker protocol compatible encoding. | 109 | -- | HTTP tracker protocol compatible encoding. |
110 | instance QueryValueLike Event where | 110 | instance QueryValueLike Event where |
@@ -174,7 +174,7 @@ data AnnounceQuery = AnnounceQuery | |||
174 | , reqEvent :: Maybe Event | 174 | , reqEvent :: Maybe Event |
175 | } deriving (Show, Eq, Typeable) | 175 | } deriving (Show, Eq, Typeable) |
176 | 176 | ||
177 | $(deriveJSON (L.map toLower . L.dropWhile isLower) ''AnnounceQuery) | 177 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''AnnounceQuery) |
178 | 178 | ||
179 | -- | UDP tracker protocol compatible encoding. | 179 | -- | UDP tracker protocol compatible encoding. |
180 | instance Serialize AnnounceQuery where | 180 | instance Serialize AnnounceQuery where |
@@ -416,7 +416,7 @@ data AnnounceInfo = | |||
416 | , respWarning :: !(Maybe Text) | 416 | , respWarning :: !(Maybe Text) |
417 | } deriving (Show, Typeable) | 417 | } deriving (Show, Typeable) |
418 | 418 | ||
419 | $(deriveJSON (L.map toLower . L.dropWhile isLower) ''AnnounceInfo) | 419 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''AnnounceInfo) |
420 | 420 | ||
421 | -- | HTTP tracker protocol compatible encoding. | 421 | -- | HTTP tracker protocol compatible encoding. |
422 | instance BEncode AnnounceInfo where | 422 | instance BEncode AnnounceInfo where |
@@ -561,7 +561,7 @@ data ScrapeEntry = ScrapeEntry { | |||
561 | , siName :: !(Maybe Text) | 561 | , siName :: !(Maybe Text) |
562 | } deriving (Show, Eq, Typeable) | 562 | } deriving (Show, Eq, Typeable) |
563 | 563 | ||
564 | $(deriveJSON (L.map toLower . L.dropWhile isLower) ''ScrapeEntry) | 564 | $(deriveJSON defaultOptions { fieldLabelModifier = (L.map toLower . L.dropWhile isLower) } ''ScrapeEntry) |
565 | 565 | ||
566 | -- | HTTP tracker protocol compatible encoding. | 566 | -- | HTTP tracker protocol compatible encoding. |
567 | instance BEncode ScrapeEntry where | 567 | instance BEncode ScrapeEntry where |