summaryrefslogtreecommitdiff
path: root/src/Data/Torrent
diff options
context:
space:
mode:
authorSam Truzjan <pxqr.sta@gmail.com>2013-11-28 13:57:59 +0400
committerSam Truzjan <pxqr.sta@gmail.com>2013-11-28 13:57:59 +0400
commit6cb3526b16429ea772911d9ff55c5b940a83cdb3 (patch)
treee56c0bc28eeb1d91e79431e14615a1677aba8724 /src/Data/Torrent
parent12d95bc5880b9fe73fe9cb113f901077376ce8af (diff)
Move URN to separate module
Diffstat (limited to 'src/Data/Torrent')
-rw-r--r--src/Data/Torrent/URN.hs133
1 files changed, 133 insertions, 0 deletions
diff --git a/src/Data/Torrent/URN.hs b/src/Data/Torrent/URN.hs
new file mode 100644
index 00000000..cb3aef02
--- /dev/null
+++ b/src/Data/Torrent/URN.hs
@@ -0,0 +1,133 @@
1-- |
2-- Copyright : (c) Sam Truzjan 2013
3-- License : BSD3
4-- Maintainer : pxqr.sta@gmail.com
5-- Stability : experimental
6-- Portability : portable
7--
8-- URN is pesistent location-independent identifier for
9-- resources. In particular, URNs are used represent torrent names
10-- as a part of magnet link, see 'Data.Torrent.Magnet.Magnet' for
11-- more info.
12--
13{-# LANGUAGE MultiParamTypeClasses #-}
14{-# LANGUAGE DeriveDataTypeable #-}
15module Data.Torrent.URN
16 ( -- * Namespaces
17 NamespaceId
18 , btih
19
20 -- * URN
21 , URN (..)
22
23 -- ** Construction
24 , infohashURN
25
26 -- ** Conversion
27 , parseURN
28 , renderURN
29 ) where
30
31import Control.Applicative
32import Data.Convertible
33import Data.Default
34import Data.List as L
35import Data.String
36import Data.Text as T
37import Data.Typeable
38import Network.HTTP.Types.QueryLike
39import Text.PrettyPrint
40import Text.PrettyPrint.Class
41
42import Data.Torrent.InfoHash
43
44
45-- | Namespace identifier determines the syntactic interpretation of
46-- namespace-specific string.
47type NamespaceId = [Text]
48
49-- | BitTorrent Info Hash (hence the name) namespace
50-- identifier. Namespace-specific string /should/ be a base16\/base32
51-- encoded SHA1 hash of the corresponding torrent /info/ dictionary.
52--
53btih :: NamespaceId
54btih = ["btih"]
55
56-- | Uniform Resource Name - location-independent, resource
57-- identifier.
58--
59data URN = URN
60 { urnNamespace :: NamespaceId -- ^ a namespace identifier;
61 , urnString :: Text -- ^ a corresponding
62 -- namespace-specific string.
63 } deriving (Eq, Ord, Typeable)
64
65{-----------------------------------------------------------------------
66-- Infohash convertion
67-----------------------------------------------------------------------}
68
69instance Convertible URN InfoHash where
70 safeConvert u @ URN {..}
71 | urnNamespace /= btih = convError "invalid namespace" u
72 | otherwise = safeConvert urnString
73
74-- | Make resource name for torrent with corresponding
75-- infohash. Infohash is base16 (hex) encoded).
76--
77infohashURN :: InfoHash -> URN
78infohashURN = URN btih . longHex
79
80-- | Meaningless placeholder value.
81instance Default URN where
82 def = infohashURN def
83
84{-----------------------------------------------------------------------
85-- Rendering
86-----------------------------------------------------------------------}
87
88-- | Render URN to its text representation.
89renderURN :: URN -> Text
90renderURN URN {..}
91 = T.intercalate ":" $ "urn" : urnNamespace ++ [urnString]
92
93instance Pretty URN where
94 pretty = text . T.unpack . renderURN
95
96instance Show URN where
97 showsPrec n = showsPrec n . T.unpack . renderURN
98
99instance QueryValueLike URN where
100 toQueryValue = toQueryValue . renderURN
101 {-# INLINE toQueryValue #-}
102
103{-----------------------------------------------------------------------
104-- Parsing
105-----------------------------------------------------------------------}
106
107unsnoc :: [a] -> Maybe ([a], a)
108unsnoc [] = Nothing
109unsnoc xs = Just (L.init xs, L.last xs)
110
111instance Convertible Text URN where
112 safeConvert t = case T.split (== ':') t of
113 uriScheme : body
114 | T.toLower uriScheme == "urn" ->
115 case unsnoc body of
116 Just (namespace, val) -> pure URN
117 { urnNamespace = namespace
118 , urnString = val
119 }
120 Nothing -> convError "missing URN string" body
121 | otherwise -> convError "invalid URN scheme" uriScheme
122 [] -> convError "missing URN scheme" t
123
124instance IsString URN where
125 fromString = either (error . prettyConvertError) id
126 . safeConvert . T.pack
127
128-- | Try to parse an URN from its text representation.
129--
130-- Use 'safeConvert' for detailed error messages.
131--
132parseURN :: Text -> Maybe URN
133parseURN = either (const Nothing) pure . safeConvert