summaryrefslogtreecommitdiff
path: root/src/Data/Torrent/InfoHash.hs
diff options
context:
space:
mode:
Diffstat (limited to 'src/Data/Torrent/InfoHash.hs')
-rw-r--r--src/Data/Torrent/InfoHash.hs94
1 files changed, 63 insertions, 31 deletions
diff --git a/src/Data/Torrent/InfoHash.hs b/src/Data/Torrent/InfoHash.hs
index e9e6cf39..25fd3e49 100644
--- a/src/Data/Torrent/InfoHash.hs
+++ b/src/Data/Torrent/InfoHash.hs
@@ -9,6 +9,8 @@
9-- 9--
10{-# LANGUAGE FlexibleInstances #-} 10{-# LANGUAGE FlexibleInstances #-}
11{-# LANGUAGE GeneralizedNewtypeDeriving #-} 11{-# LANGUAGE GeneralizedNewtypeDeriving #-}
12{-# LANGUAGE MultiParamTypeClasses #-}
13{-# LANGUAGE DeriveDataTypeable #-}
12module Data.Torrent.InfoHash 14module Data.Torrent.InfoHash
13 ( InfoHash 15 ( InfoHash
14 16
@@ -29,20 +31,21 @@ import Data.Aeson
29import Data.BEncode 31import Data.BEncode
30import Data.ByteString as BS 32import Data.ByteString as BS
31import Data.ByteString.Char8 as BC 33import Data.ByteString.Char8 as BC
32import Data.ByteString.Lazy as BL
33import Data.ByteString.Base16 as Base16 34import Data.ByteString.Base16 as Base16
34import Data.ByteString.Base32 as Base32 35import Data.ByteString.Base32 as Base32
35import qualified Data.ByteString.Lazy.Builder as B 36import Data.ByteString.Base64 as Base64
36import qualified Data.ByteString.Lazy.Builder.ASCII as B
37import Data.Char 37import Data.Char
38import Data.Convertible.Base
39import Data.Default
38import Data.List as L 40import Data.List as L
39import Data.Maybe 41import Data.Maybe
40import Data.Hashable as Hashable 42import Data.Hashable as Hashable
41import Data.URLEncoded as URL
42import Data.Serialize 43import Data.Serialize
43import Data.String 44import Data.String
44import Data.Text as T 45import Data.Text as T
45import Data.Text.Encoding as T 46import Data.Text.Encoding as T
47import Data.Typeable
48import Network.HTTP.Types.QueryLike
46import Network.URI 49import Network.URI
47import Numeric 50import Numeric
48import Text.ParserCombinators.ReadP as P 51import Text.ParserCombinators.ReadP as P
@@ -62,7 +65,13 @@ import Text.PrettyPrint.Class
62 65
63-- | Exactly 20 bytes long SHA1 hash of the info part of torrent file. 66-- | Exactly 20 bytes long SHA1 hash of the info part of torrent file.
64newtype InfoHash = InfoHash { getInfoHash :: BS.ByteString } 67newtype InfoHash = InfoHash { getInfoHash :: BS.ByteString }
65 deriving (Eq, Ord) 68 deriving (Eq, Ord, Typeable)
69
70infoHashLen :: Int
71infoHashLen = 20
72
73instance Default InfoHash where
74 def = "0123456789012345678901234567890123456789"
66 75
67-- | for hex encoded strings 76-- | for hex encoded strings
68instance Show InfoHash where 77instance Show InfoHash where
@@ -88,52 +97,76 @@ instance IsString InfoHash where
88 97
89instance Hashable InfoHash where 98instance Hashable InfoHash where
90 hash = Hashable.hash . getInfoHash 99 hash = Hashable.hash . getInfoHash
100 {-# INLINE hash #-}
91 101
102-- | Raw bytes.
92instance BEncode InfoHash where 103instance BEncode InfoHash where
93 toBEncode = toBEncode . getInfoHash 104 toBEncode = toBEncode . getInfoHash
94 fromBEncode be = InfoHash <$> fromBEncode be 105 fromBEncode be = InfoHash <$> fromBEncode be
95 106
107-- | Raw bytes.
96instance Serialize InfoHash where 108instance Serialize InfoHash where
97 put = putByteString . getInfoHash 109 put = putByteString . getInfoHash
98 get = InfoHash <$> getBytes 20 110 get = InfoHash <$> getBytes 20
99 111
100-- | Represented as base16 encoded string. 112-- | base16 encoded string.
101instance ToJSON InfoHash where 113instance ToJSON InfoHash where
102 toJSON (InfoHash ih) = String $ T.decodeUtf8 $ Base16.encode ih 114 toJSON (InfoHash ih) = String $ T.decodeUtf8 $ Base16.encode ih
103 115
104-- | Can be base16 or base32 encoded string. 116-- | Can be base16 or base32 encoded string.
105instance FromJSON InfoHash where 117instance FromJSON InfoHash where
106 parseJSON = withText "JSON" $ 118 parseJSON = withText "JSON" $ -- TODO
107 maybe (fail "could not parse InfoHash") pure . textToInfoHash 119 maybe (fail "could not parse InfoHash") pure . textToInfoHash
108 120
109instance URLShow InfoHash where 121-- | Raw bytes.
110 urlShow = show 122instance QueryValueLike InfoHash where
123 toQueryValue (InfoHash ih) = Just ih
124 {-# INLINE toQueryValue #-}
111 125
112-- | base16 encoded. 126-- | base16 encoded.
113instance Pretty InfoHash where 127instance Pretty InfoHash where
114 pretty = text . BC.unpack . ppHex . getInfoHash 128 pretty = text . T.unpack . longHex
115
116infoHashLen :: Int
117infoHashLen = 20
118 129
119-- | Convert raw bytes to info hash. 130-- | Convert raw bytes to info hash.
131instance Convertible BS.ByteString InfoHash where
132 safeConvert bs
133 | BS.length bs == infoHashLen = pure (InfoHash bs)
134 | otherwise = convError "invalid length" bs
135
136-- | Parse infohash from base16\/base32\/base64 encoded string.
137instance Convertible Text InfoHash where
138 safeConvert t
139 | hashLen <= 28 =
140 case Base64.decode hashStr of
141 Left msg -> convError ("invalid base64 encoding" ++ msg) t
142 Right ihStr -> pure $ InfoHash ihStr
143
144 | hashLen == 32 = pure $ InfoHash $ Base32.decode hashStr
145-- TODO FIX Base32.decode can return 'undefined'
146
147 | hashLen == 40 =
148 let (ihStr, inv) = Base16.decode hashStr
149 in if BS.length inv == 0
150 then pure $ InfoHash ihStr
151 else convError "invalid base16 encoding" t
152
153 | otherwise = convError "invalid length" t
154 where
155 hashLen = BS.length hashStr
156 hashStr = T.encodeUtf8 t
157
158ignoreErrorMsg :: Either a b -> Maybe b
159ignoreErrorMsg = either (const Nothing) Just
160
161-- | TODO remove from API
120byteStringToInfoHash :: BS.ByteString -> Maybe InfoHash 162byteStringToInfoHash :: BS.ByteString -> Maybe InfoHash
121byteStringToInfoHash bs 163byteStringToInfoHash = ignoreErrorMsg . safeConvert
122 | BS.length bs == infoHashLen = Just (InfoHash bs)
123 | otherwise = Nothing
124 164
125-- | Tries both base16 and base32 while decoding info hash. 165-- | Tries both base16 and base32 while decoding info hash. To Use
166-- 'safeConvert' to find out
167--
126textToInfoHash :: Text -> Maybe InfoHash 168textToInfoHash :: Text -> Maybe InfoHash
127textToInfoHash t 169textToInfoHash = ignoreErrorMsg . safeConvert
128 | hashLen == 32 = Just $ InfoHash $ Base32.decode hashStr
129 | hashLen == 40 = let (ihStr, inv) = Base16.decode hashStr
130 in if BS.length inv == 0
131 then Just $ InfoHash ihStr
132 else Nothing
133 | otherwise = Nothing
134 where
135 hashLen = BS.length hashStr
136 hashStr = T.encodeUtf8 t
137 170
138-- | Hex encode infohash to text, full length. 171-- | Hex encode infohash to text, full length.
139longHex :: InfoHash -> Text 172longHex :: InfoHash -> Text
@@ -143,10 +176,9 @@ longHex = T.decodeUtf8 . Base16.encode . getInfoHash
143shortHex :: InfoHash -> Text 176shortHex :: InfoHash -> Text
144shortHex = T.take 7 . longHex 177shortHex = T.take 7 . longHex
145 178
146ppHex :: BS.ByteString -> BS.ByteString 179-- | TODO remove from API
147ppHex = BL.toStrict . B.toLazyByteString . B.byteStringHexFixed 180--
148 181-- Add query info hash parameter to uri.
149-- | Add query info hash parameter to uri.
150-- 182--
151-- > info_hash=<url_encoded_info_hash> 183-- > info_hash=<url_encoded_info_hash>
152-- 184--