summaryrefslogtreecommitdiff
path: root/src
diff options
context:
space:
mode:
Diffstat (limited to 'src')
-rw-r--r--src/Data/Torrent/Magnet.hs289
1 files changed, 140 insertions, 149 deletions
diff --git a/src/Data/Torrent/Magnet.hs b/src/Data/Torrent/Magnet.hs
index 791537b1..1a675be4 100644
--- a/src/Data/Torrent/Magnet.hs
+++ b/src/Data/Torrent/Magnet.hs
@@ -13,7 +13,11 @@
13-- Bittorrent specific info: 13-- Bittorrent specific info:
14-- <http://www.bittorrent.org/beps/bep_0009.html> 14-- <http://www.bittorrent.org/beps/bep_0009.html>
15-- 15--
16{-# LANGUAGE NamedFieldPuns #-} 16{-# LANGUAGE NamedFieldPuns #-}
17{-# LANGUAGE FlexibleInstances #-}
18{-# LANGUAGE MultiParamTypeClasses #-}
19{-# LANGUAGE TypeSynonymInstances #-}
20{-# LANGUAGE DeriveDataTypeable #-}
17module Data.Torrent.Magnet 21module Data.Torrent.Magnet
18 ( -- * Magnet 22 ( -- * Magnet
19 Magnet(..) 23 Magnet(..)
@@ -26,85 +30,32 @@ module Data.Torrent.Magnet
26 -- * Conversion 30 -- * Conversion
27 , parseMagnet 31 , parseMagnet
28 , renderMagnet 32 , renderMagnet
29
30 -- ** Extra
31 , fromURI
32 , toURI
33 ) where 33 ) where
34 34
35import Control.Applicative 35import Control.Applicative
36import Control.Monad 36import Control.Monad
37import Data.ByteString.Char8 as BC
38import Data.Convertible
39import Data.Default
37import Data.Map as M 40import Data.Map as M
38import Data.Maybe 41import Data.Maybe
39import Data.List as L 42import Data.List as L
40import Data.URLEncoded as URL
41import Data.String 43import Data.String
42import Data.Text as T 44import Data.Text as T
43import Data.Text.Encoding as T 45import Data.Text.Encoding as T
46import Data.Text.Read
47import Data.Typeable
48import Network.HTTP.Types.QueryLike
49import Network.HTTP.Types.URI
44import Network.URI 50import Network.URI
45import Text.Read
46import Text.PrettyPrint as PP 51import Text.PrettyPrint as PP
47import Text.PrettyPrint.Class 52import Text.PrettyPrint.Class
48 53
49import Data.Torrent 54import Data.Torrent
50import Data.Torrent.InfoHash 55import Data.Torrent.InfoHash
51import Data.Torrent.Layout 56import Data.Torrent.Layout
57import Data.Torrent.URN
52 58
53{-----------------------------------------------------------------------
54-- URN
55-----------------------------------------------------------------------}
56
57type NamespaceId = [Text]
58
59btih :: NamespaceId
60btih = ["btih"]
61
62-- | Uniform Resource Name - location-independent, resource
63-- identifier.
64data URN = URN
65 { urnNamespace :: NamespaceId
66 , urnString :: Text
67 } deriving (Eq, Ord)
68
69instance Show URN where
70 showsPrec n = showsPrec n . T.unpack . renderURN
71
72instance IsString URN where
73 fromString = fromMaybe def . parseURN . T.pack
74 where
75 def = error "unable to parse URN"
76
77instance URLShow URN where
78 urlShow = T.unpack . renderURN
79
80parseURN :: Text -> Maybe URN
81parseURN str = case T.split (== ':') str of
82 uriScheme : body
83 | T.toLower uriScheme == "urn" -> mkURN body
84 | otherwise -> Nothing
85 [] -> Nothing
86 where
87 mkURN [] = Nothing
88 mkURN xs = Just $ URN
89 { urnNamespace = L.init xs
90 , urnString = L.last xs
91 }
92
93renderURN :: URN -> Text
94renderURN URN {..}
95 = T.intercalate ":" $ "urn" : urnNamespace ++ [urnString]
96
97urnToInfoHash :: URN -> Maybe InfoHash
98urnToInfoHash (URN {..})
99 | urnNamespace /= btih = Nothing
100 | otherwise = textToInfoHash urnString
101
102infoHashToURN :: InfoHash -> URN
103infoHashToURN = URN btih . T.pack . show
104
105{-----------------------------------------------------------------------
106-- Magnet
107-----------------------------------------------------------------------}
108 59
109-- TODO multiple exact topics 60-- TODO multiple exact topics
110-- TODO supplement 61-- TODO supplement
@@ -113,14 +64,17 @@ infoHashToURN = URN btih . T.pack . show
113data Magnet = Magnet 64data Magnet = Magnet
114 { -- | Resource hash. 65 { -- | Resource hash.
115 exactTopic :: !InfoHash 66 exactTopic :: !InfoHash
67
116 -- | Might be used to display name while waiting for metadata. 68 -- | Might be used to display name while waiting for metadata.
117 , displayName :: Maybe Text 69 , displayName :: Maybe Text
70
118 -- | Size of the resource in bytes. 71 -- | Size of the resource in bytes.
119 , exactLength :: Maybe Integer 72 , exactLength :: Maybe Integer
120 73
121 , manifest :: Maybe String 74 , manifest :: Maybe Text
75
122 -- | Search string. 76 -- | Search string.
123 , keywordTopic :: Maybe String 77 , keywordTopic :: Maybe Text
124 78
125 , acceptableSource :: Maybe URI 79 , acceptableSource :: Maybe URI
126 , exactSource :: Maybe URI 80 , exactSource :: Maybe URI
@@ -128,32 +82,98 @@ data Magnet = Magnet
128 , tracker :: Maybe URI 82 , tracker :: Maybe URI
129 83
130 , supplement :: Map Text Text 84 , supplement :: Map Text Text
131 } deriving (Eq, Ord) 85 } deriving (Eq, Ord, Typeable)
86
87
88instance QueryValueLike Integer where
89 toQueryValue = toQueryValue . show
90
91instance QueryValueLike URI where
92 toQueryValue = toQueryValue . show
93
94instance QueryLike Magnet where
95 toQuery Magnet {..} =
96 [ ("xt", toQueryValue $ infohashURN exactTopic)
97 , ("dn", toQueryValue displayName)
98 , ("xl", toQueryValue exactLength)
99 , ("mt", toQueryValue manifest)
100 , ("kt", toQueryValue keywordTopic)
101 , ("as", toQueryValue acceptableSource)
102 , ("xs", toQueryValue exactSource)
103 , ("tr", toQueryValue tracker)
104 ]
105
106instance QueryValueLike Magnet where
107 toQueryValue = toQueryValue . renderMagnet
108
109instance Convertible QueryText Magnet where
110 safeConvert xs = do
111 urnStr <- getTextMsg "xt" "exact topic not defined" xs
112 infoHash <- convertVia (error "safeConvert" :: URN) urnStr
113 return Magnet
114 { exactTopic = infoHash
115 , displayName = getText "dn" xs
116 , exactLength = getText "xl" xs >>= getInt
117 , manifest = getText "mt" xs
118 , keywordTopic = getText "kt" xs
119 , acceptableSource = getText "as" xs >>= getURI
120 , exactSource = getText "xs" xs >>= getURI
121 , tracker = getText "tr" xs >>= getURI
122 , supplement = M.empty
123 }
124 where
125 getInt = either (const Nothing) (Just . fst) . signed decimal
126 getURI = parseURI . T.unpack
127 getText p = join . L.lookup p
128 getTextMsg p msg ps = maybe (convError msg xs) pure $ getText p ps
132 129
133instance Show Magnet where 130magnetScheme :: URI
134 show = renderMagnet 131magnetScheme = URI
135 {-# INLINE show #-} 132 { uriScheme = "magnet:"
133 , uriAuthority = Nothing
134 , uriPath = ""
135 , uriQuery = ""
136 , uriFragment = ""
137 }
136 138
137instance Read Magnet where 139isMagnetURI :: URI -> Bool
138 readsPrec _ xs 140isMagnetURI u = u { uriQuery = "" } == magnetScheme
139 | Just m <- parseMagnet mstr = [(m, rest)]
140 | otherwise = []
141 where
142 (mstr, rest) = L.break (== ' ') xs
143 141
144instance IsString Magnet where 142-- | Can be used instead of 'parseMagnet'.
145 fromString = fromMaybe def . parseMagnet 143instance Convertible URI Magnet where
146 where 144 safeConvert u @ URI {..}
147 def = error "unable to parse magnet" 145 | not (isMagnetURI u) = convError "this is not a magnet link" u
146 | otherwise = safeConvert $ parseQueryText $ BC.pack uriQuery
148 147
149instance URLEncode Magnet where 148-- | Can be used instead of 'renderMagnet'.
150 urlEncode = toQuery 149instance Convertible Magnet URI where
151 {-# INLINE urlEncode #-} 150 safeConvert m = pure $ magnetScheme
151 { uriQuery = BC.unpack $ renderQuery True $ toQuery m }
152 152
153instance Pretty Magnet where 153instance Convertible String Magnet where
154 pretty = PP.text . renderMagnet 154 safeConvert str
155 | Just uri <- parseURI str = safeConvert uri
156 | otherwise = convError "unable to parse uri" str
157
158{-----------------------------------------------------------------------
159-- Construction
160-----------------------------------------------------------------------}
155 161
156-- | Set exact topic only, other params are empty. 162-- | Meaningless placeholder value.
163instance Default Magnet where
164 def = Magnet
165 { exactTopic = def
166 , displayName = Nothing
167 , exactLength = Nothing
168 , manifest = Nothing
169 , keywordTopic = Nothing
170 , acceptableSource = Nothing
171 , exactSource = Nothing
172 , tracker = Nothing
173 , supplement = M.empty
174 }
175
176-- | Set 'exactTopic' ('xt' param) only, other params are empty.
157nullMagnet :: InfoHash -> Magnet 177nullMagnet :: InfoHash -> Magnet
158nullMagnet u = Magnet 178nullMagnet u = Magnet
159 { exactTopic = u 179 { exactTopic = u
@@ -167,17 +187,16 @@ nullMagnet u = Magnet
167 , supplement = M.empty 187 , supplement = M.empty
168 } 188 }
169 189
170-- | A simple magnet link including infohash ('xt' param) and display 190-- | Like 'nullMagnet' but also include 'displayName' ('dn' param).
171-- name ('dn' param).
172--
173simpleMagnet :: Torrent -> Magnet 191simpleMagnet :: Torrent -> Magnet
174simpleMagnet Torrent {tInfoDict = InfoDict {..}} 192simpleMagnet Torrent {tInfoDict = InfoDict {..}}
175 = (nullMagnet idInfoHash) 193 = (nullMagnet idInfoHash)
176 { displayName = Just $ T.decodeUtf8 $ suggestedName idLayoutInfo 194 { displayName = Just $ T.decodeUtf8 $ suggestedName idLayoutInfo
177 } 195 }
178 196
179-- | Like 'simpleMagnet' but also include exactLength ('xl' param) and 197-- | Like 'simpleMagnet' but also include 'exactLength' ('xl' param) and
180-- tracker ('tr' param). 198-- 'tracker' ('tr' param).
199--
181detailedMagnet :: Torrent -> Magnet 200detailedMagnet :: Torrent -> Magnet
182detailedMagnet t @ Torrent {tInfoDict = InfoDict {..}, tAnnounce} 201detailedMagnet t @ Torrent {tInfoDict = InfoDict {..}, tAnnounce}
183 = (simpleMagnet t) 202 = (simpleMagnet t)
@@ -185,71 +204,43 @@ detailedMagnet t @ Torrent {tInfoDict = InfoDict {..}, tAnnounce}
185 , tracker = Just tAnnounce 204 , tracker = Just tAnnounce
186 } 205 }
187 206
188fromQuery :: URLEncoded -> Either String Magnet 207{-----------------------------------------------------------------------
189fromQuery q 208-- Conversion
190 | Just urnStr <- URL.lookup ("xt" :: String) q 209-----------------------------------------------------------------------}
191 , Just urn <- parseURN $ T.pack urnStr
192 , Just infoHash <- urnToInfoHash urn
193 = return $ Magnet
194 { exactTopic = infoHash
195 , displayName = T.pack <$> URL.lookup ("dn" :: String) q
196 , exactLength = readMaybe =<< URL.lookup ("xl" :: String) q
197
198 , manifest = URL.lookup ("mt" :: String) q
199 , keywordTopic = URL.lookup ("kt" :: String) q
200
201 , acceptableSource = parseURI =<< URL.lookup ("as" :: String) q
202 , exactSource = parseURI =<< URL.lookup ("xs" :: String) q
203
204 , tracker = parseURI =<< URL.lookup ("tr" :: String) q
205 , supplement = M.empty
206 }
207
208 | otherwise = Left "exact topic not defined"
209
210toQuery :: Magnet -> URLEncoded
211toQuery Magnet {..}
212 = s "xt" %= infoHashToURN exactTopic
213 %& s "dn" %=? (T.unpack <$> displayName)
214 %& s "xl" %=? exactLength
215 %& s "mt" %=? manifest
216 %& s "kt" %=? keywordTopic
217 %& s "as" %=? acceptableSource
218 %& s "xs" %=? exactSource
219 %& s "tr" %=? tracker
220 where
221 s :: String -> String; s = id
222 210
223magnetScheme :: URI 211parseMagnetStr :: String -> Maybe Magnet
224magnetScheme = URI 212parseMagnetStr = either (const Nothing) Just . safeConvert
225 { uriScheme = "magnet:"
226 , uriAuthority = Nothing
227 , uriPath = ""
228 , uriQuery = ""
229 , uriFragment = ""
230 }
231 213
232isMagnetURI :: URI -> Bool 214renderMagnetStr :: Magnet -> String
233isMagnetURI u = u { uriQuery = "" } == magnetScheme 215renderMagnetStr = show . (convert :: Magnet -> URI)
216
217instance Pretty Magnet where
218 pretty = PP.text . renderMagnetStr
234 219
235-- | The same as 'parseMagnet' but useful if you alread have a parsed 220instance Show Magnet where
236-- uri. 221 show = renderMagnetStr
237fromURI :: URI -> Either String Magnet 222 {-# INLINE show #-}
238fromURI u @ URI {..}
239 | not (isMagnetURI u) = Left "this is not a magnet link"
240 | otherwise = importURI u >>= fromQuery
241 223
242-- | The same as 'renderMagnet' but useful if you need an uri. 224instance Read Magnet where
243toURI :: Magnet -> URI 225 readsPrec _ xs
244toURI m = magnetScheme %? urlEncode m 226 | Just m <- parseMagnetStr mstr = [(m, rest)]
227 | otherwise = []
228 where
229 (mstr, rest) = L.break (== ' ') xs
245 230
246etom :: Either a b -> Maybe b 231instance IsString Magnet where
247etom = either (const Nothing) Just 232 fromString str = fromMaybe (error msg) $ parseMagnetStr str
233 where
234 msg = "unable to parse magnet: " ++ str
248 235
249-- | Try to parse magnet link from urlencoded string. 236-- | Try to parse magnet link from urlencoded string. Use
250parseMagnet :: String -> Maybe Magnet 237-- 'safeConvert' to find out error location.
251parseMagnet = parseURI >=> etom . fromURI 238--
239parseMagnet :: Text -> Maybe Magnet
240parseMagnet = parseMagnetStr . T.unpack
241{-# INLINE parseMagnet #-}
252 242
253-- | Render magnet link to urlencoded string 243-- | Render magnet link to urlencoded string
254renderMagnet :: Magnet -> String 244renderMagnet :: Magnet -> Text
255renderMagnet = show . toURI 245renderMagnet = T.pack . renderMagnetStr
246{-# INLINE renderMagnet #-}