summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-11-29 19:28:30 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-11-29 19:28:30 +0400
commit8e9896c5d03ba2362e5068151106f756f0a002a1 (patch)
treecfb508c8b13b3442592c5af0e1163d00aca7ff49 /src
parent10b16409b44e0f11db57e52d6ddd1f95a4eb7aec (diff)
Remove byteStringToPeerId to simplify API
Diffstat (limited to 'src')
-rw-r--r--src/Network/BitTorrent/Core/PeerId.hs15
-rw-r--r--src/Network/BitTorrent/Tracker/Message.hs8
2 files changed, 13 insertions, 10 deletions
diff --git a/src/Network/BitTorrent/Core/PeerId.hs b/src/Network/BitTorrent/Core/PeerId.hs
index 8bd175e5..148f550d 100644
--- a/src/Network/BitTorrent/Core/PeerId.hs
+++ b/src/Network/BitTorrent/Core/PeerId.hs
@@ -12,10 +12,11 @@
12-- /peer handshakes/ and used in DHT queries. 12-- /peer handshakes/ and used in DHT queries.
13-- 13--
14{-# LANGUAGE GeneralizedNewtypeDeriving #-} 14{-# LANGUAGE GeneralizedNewtypeDeriving #-}
15{-# LANGUAGE MultiParamTypeClasses #-}
16{-# LANGUAGE DeriveDataTypeable #-}
15module Network.BitTorrent.Core.PeerId 17module Network.BitTorrent.Core.PeerId
16 ( -- * PeerId 18 ( -- * PeerId
17 PeerId 19 PeerId
18 , byteStringToPeerId
19 20
20 -- * Generation 21 -- * Generation
21 , genPeerId 22 , genPeerId
@@ -40,6 +41,7 @@ import Data.ByteString.Internal as BS
40import Data.ByteString.Char8 as BC 41import Data.ByteString.Char8 as BC
41import qualified Data.ByteString.Lazy as BL 42import qualified Data.ByteString.Lazy as BL
42import qualified Data.ByteString.Lazy.Builder as BS 43import qualified Data.ByteString.Lazy.Builder as BS
44import Data.Convertible
43import Data.Default 45import Data.Default
44import Data.Foldable (foldMap) 46import Data.Foldable (foldMap)
45import Data.List as L 47import Data.List as L
@@ -51,6 +53,7 @@ import Data.Serialize as S
51import Data.String 53import Data.String
52import Data.Time.Clock (getCurrentTime) 54import Data.Time.Clock (getCurrentTime)
53import Data.Time.Format (formatTime) 55import Data.Time.Format (formatTime)
56import Data.Typeable
54import Data.Version (Version(Version), versionBranch) 57import Data.Version (Version(Version), versionBranch)
55import Network.HTTP.Types.QueryLike 58import Network.HTTP.Types.QueryLike
56import System.Entropy (getEntropy) 59import System.Entropy (getEntropy)
@@ -65,7 +68,7 @@ import Data.Torrent.Client
65 68
66-- | Peer identifier is exactly 20 bytes long bytestring. 69-- | Peer identifier is exactly 20 bytes long bytestring.
67newtype PeerId = PeerId { getPeerId :: ByteString } 70newtype PeerId = PeerId { getPeerId :: ByteString }
68 deriving (Show, Eq, Ord, BEncode, ToJSON, FromJSON) 71 deriving (Show, Eq, Ord, BEncode, ToJSON, FromJSON, Typeable)
69 72
70peerIdLen :: Int 73peerIdLen :: Int
71peerIdLen = 20 74peerIdLen = 20
@@ -92,10 +95,10 @@ instance IsString PeerId where
92instance Pretty PeerId where 95instance Pretty PeerId where
93 pretty = text . BC.unpack . getPeerId 96 pretty = text . BC.unpack . getPeerId
94 97
95byteStringToPeerId :: BS.ByteString -> Maybe PeerId 98instance Convertible BS.ByteString PeerId where
96byteStringToPeerId bs 99 safeConvert bs
97 | BS.length bs == peerIdLen = Just (PeerId bs) 100 | BS.length bs == peerIdLen = pure (PeerId bs)
98 | otherwise = Nothing 101 | otherwise = convError "invalid length" bs
99 102
100{----------------------------------------------------------------------- 103{-----------------------------------------------------------------------
101-- Encoding 104-- Encoding
diff --git a/src/Network/BitTorrent/Tracker/Message.hs b/src/Network/BitTorrent/Tracker/Message.hs
index 046f7e57..9999d128 100644
--- a/src/Network/BitTorrent/Tracker/Message.hs
+++ b/src/Network/BitTorrent/Tracker/Message.hs
@@ -267,7 +267,7 @@ instance FromParam InfoHash where
267 fromParam = either (const Nothing) pure . safeConvert 267 fromParam = either (const Nothing) pure . safeConvert
268 268
269instance FromParam PeerId where 269instance FromParam PeerId where
270 fromParam = byteStringToPeerId 270 fromParam = either (const Nothing) pure . safeConvert
271 271
272instance FromParam Word32 where 272instance FromParam Word32 where
273 fromParam = readMaybe . BC.unpack 273 fromParam = readMaybe . BC.unpack
@@ -282,9 +282,9 @@ instance FromParam PortNumber where
282 fromParam bs = fromIntegral <$> (fromParam bs :: Maybe Word32) 282 fromParam bs = fromIntegral <$> (fromParam bs :: Maybe Word32)
283 283
284instance FromParam Event where 284instance FromParam Event where
285 fromParam bs = case BC.uncons bs of 285 fromParam bs = do
286 Nothing -> Nothing 286 (x, xs) <- BC.uncons bs
287 Just (x, xs) -> readMaybe $ BC.unpack $ BC.cons (Char.toUpper x) xs 287 readMaybe $ BC.unpack $ BC.cons (Char.toUpper x) xs
288 288
289type Result = Either ParamParseFailure 289type Result = Either ParamParseFailure
290 290