summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoe Crayne <joe@jerkface.net>2019-11-29 18:56:03 -0500
committerJoe Crayne <joe@jerkface.net>2020-01-01 23:21:34 -0500
commitfddb44cc648da0494be580b832a0b5a61b27f2ff (patch)
treef981f3868a1e758f4e0b1d59b307e8be6d83bf9f
parent0d75b2bd2f6002629bbeb9d6e43a19c0fcb6ac5f (diff)
Refactored node-id appearance to Codec.AsciiKey256.
-rw-r--r--dht/dht-client.cabal2
-rw-r--r--dht/src/Codec/AsciiKey256.hs124
-rw-r--r--dht/src/Data/Tox/Msg.hs2
-rw-r--r--dht/src/Network/Tox/NodeId.hs90
4 files changed, 132 insertions, 86 deletions
diff --git a/dht/dht-client.cabal b/dht/dht-client.cabal
index c58aa82a..a2a86b95 100644
--- a/dht/dht-client.cabal
+++ b/dht/dht-client.cabal
@@ -249,7 +249,7 @@ library
249 249
250 250
251 251
252 C-sources: Presence/monitortty.c 252 C-sources: Presence/monitortty.c cbits/crc4_itu.c
253 253
254 -- if flag(aeson) 254 -- if flag(aeson)
255 build-depends: aeson, aeson-pretty, unordered-containers, vector 255 build-depends: aeson, aeson-pretty, unordered-containers, vector
diff --git a/dht/src/Codec/AsciiKey256.hs b/dht/src/Codec/AsciiKey256.hs
new file mode 100644
index 00000000..6040f454
--- /dev/null
+++ b/dht/src/Codec/AsciiKey256.hs
@@ -0,0 +1,124 @@
1{-# LANGUAGE TupleSections #-}
2module Codec.AsciiKey256 where
3
4import Control.Applicative
5import Control.Monad
6import qualified Data.ByteArray as BA
7 ;import Data.ByteArray as BA (ByteArrayAccess)
8import qualified Data.ByteString as B
9 ;import Data.ByteString (ByteString)
10import qualified Data.ByteString.Base16 as Base16
11import qualified Data.ByteString.Base32.Z as Base32
12import qualified Data.ByteString.Base64 as Base64
13import qualified Data.ByteString.Char8 as C8
14import Data.Char
15import Data.Int
16import qualified Data.Text as T
17 ;import Data.Text (Text)
18import Data.Word
19import Foreign.Ptr
20import qualified Text.ParserCombinators.ReadP as RP
21
22stripSuffix :: Text -> Text -> Maybe Text
23stripSuffix suf x = case T.splitAt (T.length x - T.length suf) x of
24 (y,end) | end == suf -> Just y
25 | otherwise -> Nothing
26
27hexdigit :: Char -> Bool
28hexdigit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'f') || ( 'A' <= c && c <= 'F')
29
30b64digit :: Char -> Bool
31b64digit '.' = True
32b64digit '+' = True
33b64digit '-' = True
34b64digit '/' = True
35b64digit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'z') || ( 'A' <= c && c <= 'Z')
36
37-- | Convert to and from a Base64 variant that uses .- instead of +/.
38nmtoken64 :: Bool -> Char -> Char
39nmtoken64 False '.' = '+'
40nmtoken64 False '-' = '/'
41nmtoken64 True '+' = '.'
42nmtoken64 True '/' = '-'
43nmtoken64 _ c = c
44
45
46-- Apply substitutions for mistaken z-base32 digits.
47fixupDigit32 :: Char -> Char
48fixupDigit32 'l' = '1'
49fixupDigit32 '2' = 'z'
50fixupDigit32 'v' = 'u'
51fixupDigit32 c = c
52
53zb32digit :: Char -> Bool
54zb32digit '1' = True
55zb32digit c = or [ '3' <= c && c <= '9'
56 , 'a' <= c && c <= 'k'
57 , 'm' <= c && c <= 'u'
58 , 'w' <= c && c <= 'z'
59 ]
60
61
62-- | Parse 43-digit base64 token into 32-byte bytestring.
63parseToken32 :: String -> Either String ByteString
64parseToken32 str = fmap (BA.drop 1) $ Base64.decode $ C8.pack $ 'A':map (nmtoken64 False) (take 43 str)
65
66-- | Encode 43-digit base64 token from 32-byte bytestring.
67showToken32 :: ByteArrayAccess bin => bin -> String
68showToken32 bs = map (nmtoken64 True) $ C8.unpack $ BA.drop 1 $ Base64.encode $ BA.cons 0 $ BA.convert bs
69
70
71-- | Parse 52-digit z-base32 token into 32-byte bytestring.
72parse32Token32 :: String -> Either String ByteString
73parse32Token32 str = fmap (BA.drop 1) $ Base32.decode $ C8.pack $ 'y':map (fixupDigit32 . toLower) (take 52 str)
74
75-- | Encode 62-digit z-base32 token from 32-byte bytestring.
76show32Token32 :: ByteArrayAccess bin => bin -> String
77show32Token32 bs = map (nmtoken64 True) $ C8.unpack $ BA.drop 1 $ Base32.encode $ BA.cons 0 $ BA.convert bs
78
79
80readsPrecKey256 :: (ByteString -> Maybe a) -> [Char] -> [(a, [Char])]
81readsPrecKey256 publicKey str
82 | (bs,_) <- Base16.decode (C8.pack $ take 64 str)
83 , Just pub <- publicKey bs
84 = [ (pub, drop (2 * B.length bs) str) ]
85 | Right bs <- parse32Token32 str
86 , Just pub <- publicKey bs
87 = [ (pub, drop 52 str) ]
88 | Right bs <- parseToken32 str
89 , Just pub <- publicKey bs
90 = [ (pub, drop 43 str) ]
91 | otherwise = []
92
93
94parseKey256 :: (Monad m, Alternative m) => String -> m ByteString
95parseKey256 nidstr = do
96 let nidbs = C8.pack nidstr
97 (bs,_) = Base16.decode nidbs
98 enid = case C8.length nidbs of
99 52 -> Base32.decode (C8.pack $ 'y' : map (fixupDigit32 . toLower) nidstr)
100 43 -> Base64.decode (C8.pack $ 'A' : map (nmtoken64 False) nidstr)
101 _ -> Left "Wrong size of key."
102 idbs <- (guard (B.length bs == 32) >> return bs)
103 <|> either fail (return . B.drop 1) enid
104 return idbs
105
106readP_key256 :: RP.ReadP ByteString
107readP_key256 = do
108 (is64,hexhash) <- foldr1 (RP.+++)
109 [ fmap (16,) (sequence $ replicate 64 (RP.satisfy isHexDigit))
110 , fmap (32,) (sequence $ replicate 52 (RP.satisfy zb32digit))
111 , fmap (64,) (sequence $ replicate 43 (RP.satisfy b64digit))
112 ]
113 let failure = fail "Bad key."
114 case is64 of
115 32 -> case Base32.decode $ C8.pack $ 'y' : map (fixupDigit32 . toLower) hexhash of
116 Right bs | B.length bs - 1==32 -> return (BA.drop 1 bs)
117 _ -> failure
118 64 -> case Base64.decode $ C8.pack $ 'A' : map (nmtoken64 False) hexhash of
119 Right bs | B.length bs - 1==32 -> return (BA.drop 1 bs)
120 _ -> failure
121 16 -> case Base16.decode $ C8.pack hexhash of
122 (bs,rem) | B.length bs == 32 && B.null rem -> return bs
123 _ -> failure
124 _ -> failure
diff --git a/dht/src/Data/Tox/Msg.hs b/dht/src/Data/Tox/Msg.hs
index 2951193d..8819faa7 100644
--- a/dht/src/Data/Tox/Msg.hs
+++ b/dht/src/Data/Tox/Msg.hs
@@ -260,7 +260,7 @@ instance Read ChatID where
260 | otherwise = [] 260 | otherwise = []
261 261
262instance Show ChatID where 262instance Show ChatID where
263 show (ChatID ed) = show64Token32 ed 263 show (ChatID ed) = showToken32 ed
264 264
265data InviteType = GroupInvite { groupName :: Text } 265data InviteType = GroupInvite { groupName :: Text }
266 | AcceptedInvite 266 | AcceptedInvite
diff --git a/dht/src/Network/Tox/NodeId.hs b/dht/src/Network/Tox/NodeId.hs
index 311095ec..68888fdd 100644
--- a/dht/src/Network/Tox/NodeId.hs
+++ b/dht/src/Network/Tox/NodeId.hs
@@ -38,7 +38,7 @@ module Network.Tox.NodeId
38 , ToxContact(..) 38 , ToxContact(..)
39 , ToxProgress(..) 39 , ToxProgress(..)
40 , parseToken32 40 , parseToken32
41 , show64Token32 41 , showToken32
42 , show32Token32 42 , show32Token32
43 , nodeInfoFromJSON 43 , nodeInfoFromJSON
44 ) where 44 ) where
@@ -91,6 +91,7 @@ import System.Endian
91import qualified Data.Text as Text 91import qualified Data.Text as Text
92 ;import Data.Text (Text) 92 ;import Data.Text (Text)
93import Util (splitJID) 93import Util (splitJID)
94import Codec.AsciiKey256
94 95
95-- | perform io for hashes that do allocation and ffi. 96-- | perform io for hashes that do allocation and ffi.
96-- unsafeDupablePerformIO is used when possible as the 97-- unsafeDupablePerformIO is used when possible as the
@@ -163,42 +164,8 @@ zeroKey = throwCryptoError $ publicKey $ B.replicate 32 0
163zeroID :: NodeId 164zeroID :: NodeId
164zeroID = NodeId (replicate 4 0) (Just zeroKey) 165zeroID = NodeId (replicate 4 0) (Just zeroKey)
165 166
166-- | Convert to and from a Base64 variant that uses .- instead of +/.
167nmtoken64 :: Bool -> Char -> Char
168nmtoken64 False '.' = '+'
169nmtoken64 False '-' = '/'
170nmtoken64 True '+' = '.'
171nmtoken64 True '/' = '-'
172nmtoken64 _ c = c
173
174-- | Parse 43-digit base64 token into 32-byte bytestring.
175parseToken32 :: String -> Either String ByteString
176parseToken32 str = fmap (BA.drop 1) $ Base64.decode $ C8.pack $ 'A':map (nmtoken64 False) (take 43 str)
177
178-- | Parse 52-digit z-base32 token into 32-byte bytestring.
179parse32Token32 :: String -> Either String ByteString
180parse32Token32 str = fmap (BA.drop 1) $ Base32.decode $ C8.pack $ 'y':map (fixupDigit32 . toLower) (take 52 str)
181
182-- | Encode 32-byte bytestring as 43-digit base64 token.
183show64Token32 :: ByteArrayAccess bin => bin -> String
184show64Token32 bs = map (nmtoken64 True) $ C8.unpack $ BA.drop 1 $ Base64.encode $ BA.cons 0 $ BA.convert bs
185
186-- | Encode 32-byte bytestring as 52-digit z-base32 token.
187show32Token32 :: ByteArrayAccess bin => bin -> String
188show32Token32 bs = map (nmtoken64 True) $ C8.unpack $ BA.drop 1 $ Base32.encode $ BA.cons 0 $ BA.convert bs
189
190instance Read NodeId where 167instance Read NodeId where
191 readsPrec _ str 168 readsPrec _ str = readsPrecKey256 (fmap key2id . maybeCryptoError . publicKey) str
192 | (bs,_) <- Base16.decode (C8.pack $ take 64 str)
193 , CryptoPassed pub <- publicKey bs -- B.length bs == 32
194 = [ (key2id pub, drop (2 * B.length bs) str) ]
195 | Right bs <- parse32Token32 str
196 , CryptoPassed pub <- publicKey bs -- B.length bs == 32
197 = [ (key2id pub, drop 52 str) ]
198 | Right bs <- parseToken32 str
199 , CryptoPassed pub <- publicKey bs -- B.length bs == 32
200 = [ (key2id pub, drop 43 str) ]
201 | otherwise = []
202 169
203instance Show NodeId where 170instance Show NodeId where
204 show nid = show32Token32 $ id2key nid 171 show nid = show32Token32 $ id2key nid
@@ -279,14 +246,7 @@ nodeInfoFromJSON prefer4 (JSON.Object v) = do
279 <|> maybe empty (return . IPv6) (ip6str >>= readMaybe) 246 <|> maybe empty (return . IPv6) (ip6str >>= readMaybe)
280 else maybe empty (return . IPv6) (ip6str >>= readMaybe) 247 else maybe empty (return . IPv6) (ip6str >>= readMaybe)
281 <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) 248 <|> maybe empty (return . IPv4) (ip4str >>= readMaybe)
282 let nidbs = C8.pack nidstr 249 idbs <- parseKey256 nidstr
283 (bs,_) = Base16.decode nidbs
284 enid = case C8.length nidbs of
285 43 -> Base64.decode (C8.pack $ 'A' : map (nmtoken64 False) nidstr)
286 52 -> Base32.decode (C8.pack $ 'y' : map (fixupDigit32 . toLower) nidstr)
287 _ -> Left "Wrong size of node-id."
288 idbs <- (guard (B.length bs == 32) >> return bs)
289 <|> either fail (return . B.drop 1) enid
290 return $ NodeInfo (bs2id idbs) ip (fromIntegral (portnum :: Word16)) 250 return $ NodeInfo (bs2id idbs) ip (fromIntegral (portnum :: Word16))
291 251
292getIP :: Word8 -> S.Get IP 252getIP :: Word8 -> S.Get IP
@@ -320,31 +280,6 @@ instance S.Serialize NodeInfo where
320 S.put port 280 S.put port
321 S.put nid 281 S.put nid
322 282
323hexdigit :: Char -> Bool
324hexdigit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'f') || ( 'A' <= c && c <= 'F')
325
326b64digit :: Char -> Bool
327b64digit '.' = True
328b64digit '+' = True
329b64digit '-' = True
330b64digit '/' = True
331b64digit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'z') || ( 'A' <= c && c <= 'Z')
332
333zb32digit :: Char -> Bool
334zb32digit '1' = True
335zb32digit c = or [ '3' <= c && c <= '9'
336 , 'a' <= c && c <= 'k'
337 , 'm' <= c && c <= 'u'
338 , 'w' <= c && c <= 'z'
339 ]
340
341-- Apply substitutions for mistaken z-base32 digits.
342fixupDigit32 :: Char -> Char
343fixupDigit32 'l' = '1'
344fixupDigit32 '2' = 'z'
345fixupDigit32 'v' = 'u'
346fixupDigit32 c = c
347
348ip_w_port :: Int -> RP.ReadP (IP, PortNumber) 283ip_w_port :: Int -> RP.ReadP (IP, PortNumber)
349ip_w_port i = do 284ip_w_port i = do
350 ip <- RP.between (RP.char '[') (RP.char ']') 285 ip <- RP.between (RP.char '[') (RP.char ']')
@@ -360,23 +295,10 @@ instance Read NodeInfo where
360 RP.skipSpaces 295 RP.skipSpaces
361 let parseAddr = RP.between (RP.char '(') (RP.char ')') (RP.munch (/=')')) 296 let parseAddr = RP.between (RP.char '(') (RP.char ')') (RP.munch (/=')'))
362 RP.+++ RP.munch (\c -> not (isSpace c) && not (c `elem` ("{}()"::[Char]))) 297 RP.+++ RP.munch (\c -> not (isSpace c) && not (c `elem` ("{}()"::[Char])))
363 nodeidAt = do (is64,hexhash) <- foldr1 (RP.+++) 298 nodeidAt = do
364 [ fmap (32,) (sequence $ replicate 52 (RP.satisfy zb32digit)) 299 nid <- bs2id <$> readP_key256
365 , fmap (64,) (sequence $ replicate 43 (RP.satisfy b64digit))
366 , fmap (16,) (sequence $ replicate 64 (RP.satisfy isHexDigit))
367 ]
368 RP.char '@' RP.+++ RP.satisfy isSpace 300 RP.char '@' RP.+++ RP.satisfy isSpace
369 addrstr <- parseAddr 301 addrstr <- parseAddr
370 nid <- case is64 of
371 32 -> case Base32.decode $ C8.pack $ 'y' : map (fixupDigit32 . toLower) hexhash of
372 Right bs | B.length bs - 1==32 -> return (bs2id $ BA.drop 1 bs)
373 _ -> fail "Bad node id."
374 64 -> case Base64.decode $ C8.pack $ 'A' : map (nmtoken64 False) hexhash of
375 Right bs | B.length bs - 1==32 -> return (bs2id $ BA.drop 1 bs)
376 _ -> fail "Bad node id."
377 _ -> case Base16.decode $ C8.pack hexhash of
378 (bs,rem) | B.length bs == 32 && B.null rem -> return (bs2id bs)
379 _ -> fail "Bad node id."
380 return (nid,addrstr) 302 return (nid,addrstr)
381 (nid,addrstr) <- ( nodeidAt RP.+++ ( (zeroID,) <$> parseAddr) ) 303 (nid,addrstr) <- ( nodeidAt RP.+++ ( (zeroID,) <$> parseAddr) )
382 (ip,port) <- case RP.readP_to_S (ip_w_port i) addrstr of 304 (ip,port) <- case RP.readP_to_S (ip_w_port i) addrstr of