diff options
Diffstat (limited to 'dht/src/Network')
-rw-r--r-- | dht/src/Network/Tox/NodeId.hs | 72 |
1 files changed, 54 insertions, 18 deletions
diff --git a/dht/src/Network/Tox/NodeId.hs b/dht/src/Network/Tox/NodeId.hs index e0169199..311095ec 100644 --- a/dht/src/Network/Tox/NodeId.hs +++ b/dht/src/Network/Tox/NodeId.hs | |||
@@ -38,7 +38,8 @@ module Network.Tox.NodeId | |||
38 | , ToxContact(..) | 38 | , ToxContact(..) |
39 | , ToxProgress(..) | 39 | , ToxProgress(..) |
40 | , parseToken32 | 40 | , parseToken32 |
41 | , showToken32 | 41 | , show64Token32 |
42 | , show32Token32 | ||
42 | , nodeInfoFromJSON | 43 | , nodeInfoFromJSON |
43 | ) where | 44 | ) where |
44 | 45 | ||
@@ -61,6 +62,7 @@ import qualified Data.ByteArray as BA | |||
61 | import qualified Data.ByteString as B | 62 | import qualified Data.ByteString as B |
62 | ;import Data.ByteString (ByteString) | 63 | ;import Data.ByteString (ByteString) |
63 | import qualified Data.ByteString.Base16 as Base16 | 64 | import qualified Data.ByteString.Base16 as Base16 |
65 | import qualified Data.ByteString.Base32.Z as Base32 | ||
64 | import qualified Data.ByteString.Base64 as Base64 | 66 | import qualified Data.ByteString.Base64 as Base64 |
65 | import qualified Data.ByteString.Char8 as C8 | 67 | import qualified Data.ByteString.Char8 as C8 |
66 | import Data.Char | 68 | import Data.Char |
@@ -173,22 +175,33 @@ nmtoken64 _ c = c | |||
173 | parseToken32 :: String -> Either String ByteString | 175 | parseToken32 :: String -> Either String ByteString |
174 | parseToken32 str = fmap (BA.drop 1) $ Base64.decode $ C8.pack $ 'A':map (nmtoken64 False) (take 43 str) | 176 | parseToken32 str = fmap (BA.drop 1) $ Base64.decode $ C8.pack $ 'A':map (nmtoken64 False) (take 43 str) |
175 | 177 | ||
178 | -- | Parse 52-digit z-base32 token into 32-byte bytestring. | ||
179 | parse32Token32 :: String -> Either String ByteString | ||
180 | parse32Token32 str = fmap (BA.drop 1) $ Base32.decode $ C8.pack $ 'y':map (fixupDigit32 . toLower) (take 52 str) | ||
181 | |||
176 | -- | Encode 32-byte bytestring as 43-digit base64 token. | 182 | -- | Encode 32-byte bytestring as 43-digit base64 token. |
177 | showToken32 :: ByteArrayAccess bin => bin -> String | 183 | show64Token32 :: ByteArrayAccess bin => bin -> String |
178 | showToken32 bs = map (nmtoken64 True) $ C8.unpack $ BA.drop 1 $ Base64.encode $ BA.cons 0 $ BA.convert bs | 184 | show64Token32 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. | ||
187 | show32Token32 :: ByteArrayAccess bin => bin -> String | ||
188 | show32Token32 bs = map (nmtoken64 True) $ C8.unpack $ BA.drop 1 $ Base32.encode $ BA.cons 0 $ BA.convert bs | ||
179 | 189 | ||
180 | instance Read NodeId where | 190 | instance Read NodeId where |
181 | readsPrec _ str | 191 | readsPrec _ str |
182 | | (bs,_) <- Base16.decode (C8.pack $ take 64 str) | 192 | | (bs,_) <- Base16.decode (C8.pack $ take 64 str) |
183 | , CryptoPassed pub <- publicKey bs -- B.length bs == 32 | 193 | , CryptoPassed pub <- publicKey bs -- B.length bs == 32 |
184 | = [ (key2id pub, drop (2 * B.length bs) str) ] | 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) ] | ||
185 | | Right bs <- parseToken32 str | 198 | | Right bs <- parseToken32 str |
186 | , CryptoPassed pub <- publicKey bs -- B.length bs == 32 | 199 | , CryptoPassed pub <- publicKey bs -- B.length bs == 32 |
187 | = [ (key2id pub, drop 43 str) ] | 200 | = [ (key2id pub, drop 43 str) ] |
188 | | otherwise = [] | 201 | | otherwise = [] |
189 | 202 | ||
190 | instance Show NodeId where | 203 | instance Show NodeId where |
191 | show nid = showToken32 $ id2key nid | 204 | show nid = show32Token32 $ id2key nid |
192 | 205 | ||
193 | instance S.Serialize NodeId where | 206 | instance S.Serialize NodeId where |
194 | get = key2id <$> getPublicKey | 207 | get = key2id <$> getPublicKey |
@@ -266,8 +279,12 @@ nodeInfoFromJSON prefer4 (JSON.Object v) = do | |||
266 | <|> maybe empty (return . IPv6) (ip6str >>= readMaybe) | 279 | <|> maybe empty (return . IPv6) (ip6str >>= readMaybe) |
267 | else maybe empty (return . IPv6) (ip6str >>= readMaybe) | 280 | else maybe empty (return . IPv6) (ip6str >>= readMaybe) |
268 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) | 281 | <|> maybe empty (return . IPv4) (ip4str >>= readMaybe) |
269 | let (bs,_) = Base16.decode (C8.pack nidstr) | 282 | let nidbs = C8.pack nidstr |
270 | enid = Base64.decode (C8.pack $ 'A' : map (nmtoken64 False) 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." | ||
271 | idbs <- (guard (B.length bs == 32) >> return bs) | 288 | idbs <- (guard (B.length bs == 32) >> return bs) |
272 | <|> either fail (return . B.drop 1) enid | 289 | <|> either fail (return . B.drop 1) enid |
273 | return $ NodeInfo (bs2id idbs) ip (fromIntegral (portnum :: Word16)) | 290 | return $ NodeInfo (bs2id idbs) ip (fromIntegral (portnum :: Word16)) |
@@ -313,6 +330,21 @@ b64digit '-' = True | |||
313 | b64digit '/' = True | 330 | b64digit '/' = True |
314 | b64digit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'z') || ( 'A' <= c && c <= 'Z') | 331 | b64digit c = ('0' <= c && c <= '9') || ( 'a' <= c && c <= 'z') || ( 'A' <= c && c <= 'Z') |
315 | 332 | ||
333 | zb32digit :: Char -> Bool | ||
334 | zb32digit '1' = True | ||
335 | zb32digit 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. | ||
342 | fixupDigit32 :: Char -> Char | ||
343 | fixupDigit32 'l' = '1' | ||
344 | fixupDigit32 '2' = 'z' | ||
345 | fixupDigit32 'v' = 'u' | ||
346 | fixupDigit32 c = c | ||
347 | |||
316 | ip_w_port :: Int -> RP.ReadP (IP, PortNumber) | 348 | ip_w_port :: Int -> RP.ReadP (IP, PortNumber) |
317 | ip_w_port i = do | 349 | ip_w_port i = do |
318 | ip <- RP.between (RP.char '[') (RP.char ']') | 350 | ip <- RP.between (RP.char '[') (RP.char ']') |
@@ -326,19 +358,23 @@ ip_w_port i = do | |||
326 | instance Read NodeInfo where | 358 | instance Read NodeInfo where |
327 | readsPrec i = RP.readP_to_S $ do | 359 | readsPrec i = RP.readP_to_S $ do |
328 | RP.skipSpaces | 360 | RP.skipSpaces |
329 | let n = 43 -- characters in node id. | 361 | let parseAddr = RP.between (RP.char '(') (RP.char ')') (RP.munch (/=')')) |
330 | parseAddr = RP.between (RP.char '(') (RP.char ')') (RP.munch (/=')')) | ||
331 | RP.+++ RP.munch (\c -> not (isSpace c) && not (c `elem` ("{}()"::[Char]))) | 362 | RP.+++ RP.munch (\c -> not (isSpace c) && not (c `elem` ("{}()"::[Char]))) |
332 | nodeidAt = do (is64,hexhash) <- | 363 | nodeidAt = do (is64,hexhash) <- foldr1 (RP.+++) |
333 | fmap (True,) (sequence $ replicate n (RP.satisfy b64digit)) | 364 | [ fmap (32,) (sequence $ replicate 52 (RP.satisfy zb32digit)) |
334 | RP.+++ fmap (False,) (sequence $ replicate 64 (RP.satisfy isHexDigit)) | 365 | , fmap (64,) (sequence $ replicate 43 (RP.satisfy b64digit)) |
366 | , fmap (16,) (sequence $ replicate 64 (RP.satisfy isHexDigit)) | ||
367 | ] | ||
335 | RP.char '@' RP.+++ RP.satisfy isSpace | 368 | RP.char '@' RP.+++ RP.satisfy isSpace |
336 | addrstr <- parseAddr | 369 | addrstr <- parseAddr |
337 | nid <- if is64 | 370 | nid <- case is64 of |
338 | then case Base64.decode $ C8.pack $ 'A' : map (nmtoken64 False) hexhash 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 | ||
339 | Right bs | B.length bs - 1==32 -> return (bs2id $ BA.drop 1 bs) | 375 | Right bs | B.length bs - 1==32 -> return (bs2id $ BA.drop 1 bs) |
340 | _ -> fail "Bad node id." | 376 | _ -> fail "Bad node id." |
341 | else case Base16.decode $ C8.pack hexhash of | 377 | _ -> case Base16.decode $ C8.pack hexhash of |
342 | (bs,rem) | B.length bs == 32 && B.null rem -> return (bs2id bs) | 378 | (bs,rem) | B.length bs == 32 && B.null rem -> return (bs2id bs) |
343 | _ -> fail "Bad node id." | 379 | _ -> fail "Bad node id." |
344 | return (nid,addrstr) | 380 | return (nid,addrstr) |
@@ -617,10 +653,10 @@ parseNoSpamJID jid = do | |||
617 | (u,h) <- maybe (Left "Invalid JID.") Right | 653 | (u,h) <- maybe (Left "Invalid JID.") Right |
618 | $ let (mu,h,_) = splitJID jid | 654 | $ let (mu,h,_) = splitJID jid |
619 | in fmap (, h) mu | 655 | in fmap (, h) mu |
620 | base64 <- case splitAt 43 $ Text.unpack h of | 656 | based <- case splitAt 52 $ Text.unpack h of |
621 | (base64,".tox") -> Right base64 | 657 | (base32,".tox") -> Right base32 |
622 | _ -> Left "Hostname should be 43 base64 digits followed by .tox." | 658 | _ -> Left "Hostname should be 52 z-base32 digits followed by .tox." |
623 | pub <- id2key <$> readEither base64 | 659 | pub <- id2key <$> readEither based |
624 | let ustr = Text.unpack u | 660 | let ustr = Text.unpack u |
625 | case ustr of | 661 | case ustr of |
626 | '$' : b64digits -> solveBase64NoSpamID b64digits pub | 662 | '$' : b64digits -> solveBase64NoSpamID b64digits pub |