summaryrefslogtreecommitdiff
path: root/dht/src/Codec/AsciiKey256.hs
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 /dht/src/Codec/AsciiKey256.hs
parent0d75b2bd2f6002629bbeb9d6e43a19c0fcb6ac5f (diff)
Refactored node-id appearance to Codec.AsciiKey256.
Diffstat (limited to 'dht/src/Codec/AsciiKey256.hs')
-rw-r--r--dht/src/Codec/AsciiKey256.hs124
1 files changed, 124 insertions, 0 deletions
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