diff options
author | joe <joe@jerkface.net> | 2017-11-22 20:12:07 -0500 |
---|---|---|
committer | joe <joe@jerkface.net> | 2017-11-22 20:12:07 -0500 |
commit | de34b6ec46a7136c249c95d97de3a569cd60b835 (patch) | |
tree | 45f9fd49484ea7bb8fec20bfdafb62edfde2f239 | |
parent | 27cb2cbe0338c19fd4f8a22b4453086288dae5c4 (diff) |
NoSpamId type to include nospam + checksum + public key.
-rw-r--r-- | src/Crypto/Tox.hs | 11 | ||||
-rw-r--r-- | src/Network/Tox/DHT/Transport.hs | 24 | ||||
-rw-r--r-- | src/Network/Tox/NodeId.hs | 104 |
3 files changed, 112 insertions, 27 deletions
diff --git a/src/Crypto/Tox.hs b/src/Crypto/Tox.hs index 9a365daa..a43e3379 100644 --- a/src/Crypto/Tox.hs +++ b/src/Crypto/Tox.hs | |||
@@ -55,6 +55,7 @@ module Crypto.Tox | |||
55 | , encryptSymmetric | 55 | , encryptSymmetric |
56 | , encodeSecret | 56 | , encodeSecret |
57 | , decodeSecret | 57 | , decodeSecret |
58 | , xorsum | ||
58 | ) where | 59 | ) where |
59 | 60 | ||
60 | import Control.Arrow | 61 | import Control.Arrow |
@@ -588,3 +589,13 @@ decodeSecret k64 = do | |||
588 | CryptoPassed x -> Just x | 589 | CryptoPassed x -> Just x |
589 | _ -> Nothing | 590 | _ -> Nothing |
590 | 591 | ||
592 | xorsum :: ByteArrayAccess ba => ba -> Word16 | ||
593 | xorsum bs = unsafeDupablePerformIO $ BA.withByteArray bs $ \ptr16 -> do | ||
594 | let (wcnt,r) = BA.length bs `divMod` 2 | ||
595 | loop cnt !ac = do | ||
596 | ac' <- xor ac <$> peekElemOff ptr16 cnt | ||
597 | case cnt of 0 -> return ac' | ||
598 | _ -> loop (cnt - 1) ac' | ||
599 | loop (wcnt - 1) $ case r of | ||
600 | 0 -> 0 | ||
601 | _ -> 256 * fromIntegral (BA.index bs (BA.length bs - 1)) | ||
diff --git a/src/Network/Tox/DHT/Transport.hs b/src/Network/Tox/DHT/Transport.hs index 2e5649d3..51ec2e80 100644 --- a/src/Network/Tox/DHT/Transport.hs +++ b/src/Network/Tox/DHT/Transport.hs | |||
@@ -260,30 +260,6 @@ data FriendRequest = FriendRequest | |||
260 | } | 260 | } |
261 | deriving (Eq, Show) | 261 | deriving (Eq, Show) |
262 | 262 | ||
263 | data NoSpam = NoSpam !Word32 !(Maybe Word16) | ||
264 | |||
265 | instance Read NoSpam where | ||
266 | readsPrec d s = case break isSpace s of | ||
267 | (ws,rs) | (length ws == 8) -> base64decode rs (NoSpam <$> get <*> (Just <$> get)) ws | ||
268 | (ws,rs) | (length ws == 12) -> base16decode rs (NoSpam <$> get <*> (Just <$> get)) ws | ||
269 | _ -> [] | ||
270 | |||
271 | base64decode :: Monad m => t1 -> Get t -> String -> m (t, t1) | ||
272 | base64decode rs getter s = | ||
273 | either fail (\a -> return (a,rs)) | ||
274 | $ runGet getter | ||
275 | =<< Base64.decode (B8.pack s) | ||
276 | |||
277 | base16decode :: Monad m => t1 -> Get t -> String -> m (t, t1) | ||
278 | base16decode rs getter s = | ||
279 | either fail (\a -> return (a,rs)) | ||
280 | $ runGet getter | ||
281 | $ fst | ||
282 | $ Base16.decode (B8.pack s) | ||
283 | |||
284 | verifyChecksum :: PublicKey -> Word16 -> Either String () | ||
285 | verifyChecksum _ _ = return () -- TODO | ||
286 | |||
287 | 263 | ||
288 | -- When sent as a DHT request packet (this is the data sent in the DHT request | 264 | -- When sent as a DHT request packet (this is the data sent in the DHT request |
289 | -- packet): | 265 | -- packet): |
diff --git a/src/Network/Tox/NodeId.hs b/src/Network/Tox/NodeId.hs index 95604108..0ffc3d22 100644 --- a/src/Network/Tox/NodeId.hs +++ b/src/Network/Tox/NodeId.hs | |||
@@ -10,6 +10,7 @@ | |||
10 | {-# LANGUAGE GADTs #-} | 10 | {-# LANGUAGE GADTs #-} |
11 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} | 11 | {-# LANGUAGE GeneralizedNewtypeDeriving #-} |
12 | {-# LANGUAGE KindSignatures #-} | 12 | {-# LANGUAGE KindSignatures #-} |
13 | {-# LANGUAGE LambdaCase #-} | ||
13 | {-# LANGUAGE PatternSynonyms #-} | 14 | {-# LANGUAGE PatternSynonyms #-} |
14 | {-# LANGUAGE ScopedTypeVariables #-} | 15 | {-# LANGUAGE ScopedTypeVariables #-} |
15 | {-# LANGUAGE TupleSections #-} | 16 | {-# LANGUAGE TupleSections #-} |
@@ -25,8 +26,14 @@ module Network.Tox.NodeId | |||
25 | , getIP | 26 | , getIP |
26 | , xorNodeId | 27 | , xorNodeId |
27 | , testNodeIdBit | 28 | , testNodeIdBit |
28 | , sampleNodeId) where | 29 | , sampleNodeId |
29 | 30 | , NoSpam(..) | |
31 | , NoSpamId(..) | ||
32 | , parseNoSpamId | ||
33 | , nospam64 | ||
34 | , verifyChecksum) where | ||
35 | |||
36 | import Debug.Trace | ||
30 | import Control.Applicative | 37 | import Control.Applicative |
31 | import Control.Arrow | 38 | import Control.Arrow |
32 | import Control.Monad | 39 | import Control.Monad |
@@ -47,6 +54,8 @@ import Data.Char | |||
47 | import Data.Data | 54 | import Data.Data |
48 | import Data.Hashable | 55 | import Data.Hashable |
49 | import Data.IP | 56 | import Data.IP |
57 | import Data.List | ||
58 | import Data.Maybe | ||
50 | import Data.Serialize as S | 59 | import Data.Serialize as S |
51 | import Data.Word | 60 | import Data.Word |
52 | import Foreign.Storable | 61 | import Foreign.Storable |
@@ -54,12 +63,16 @@ import GHC.TypeLits | |||
54 | import Network.Address hiding (nodePort) | 63 | import Network.Address hiding (nodePort) |
55 | import System.IO.Unsafe (unsafeDupablePerformIO) | 64 | import System.IO.Unsafe (unsafeDupablePerformIO) |
56 | import qualified Text.ParserCombinators.ReadP as RP | 65 | import qualified Text.ParserCombinators.ReadP as RP |
57 | import Text.Read | 66 | import Text.Read hiding (get) |
58 | import Data.Bits | 67 | import Data.Bits |
59 | import Crypto.Tox | 68 | import Crypto.Tox |
60 | import Foreign.Ptr | 69 | import Foreign.Ptr |
61 | import Data.Function | 70 | import Data.Function |
62 | import System.Endian | 71 | import System.Endian |
72 | import qualified Data.Text as Text | ||
73 | ;import Data.Text (Text) | ||
74 | import Util (splitJID) | ||
75 | import Text.Printf | ||
63 | 76 | ||
64 | -- | perform io for hashes that do allocation and ffi. | 77 | -- | perform io for hashes that do allocation and ffi. |
65 | -- unsafeDupablePerformIO is used when possible as the | 78 | -- unsafeDupablePerformIO is used when possible as the |
@@ -468,3 +481,88 @@ class KnownNat n => OnionPacket n where | |||
468 | instance OnionPacket 0 where mkOnion _ = id | 481 | instance OnionPacket 0 where mkOnion _ = id |
469 | instance OnionPacket 3 where mkOnion = OnionResponse3 | 482 | instance OnionPacket 3 where mkOnion = OnionResponse3 |
470 | -} | 483 | -} |
484 | |||
485 | data NoSpam = NoSpam !Word32 !(Maybe Word16) | ||
486 | deriving (Eq,Ord,Show) | ||
487 | |||
488 | instance Read NoSpam where | ||
489 | readsPrec d s = case break isSpace s of | ||
490 | ('$':ws ,rs) | (length ws == 8) -> base64decode rs (NoSpam <$> get <*> (Just <$> get)) ws | ||
491 | ('0':'x':ws,rs) | (length ws == 12) -> base16decode rs (NoSpam <$> get <*> (Just <$> get)) ws | ||
492 | _ -> [] | ||
493 | |||
494 | base64decode :: Monad m => t1 -> Get t -> String -> m (t, t1) | ||
495 | base64decode rs getter s = | ||
496 | either fail (\a -> return (a,rs)) | ||
497 | $ runGet getter | ||
498 | =<< Base64.decode (C8.pack $ map (nmtoken64 False) s) | ||
499 | |||
500 | base16decode :: Monad m => t1 -> Get t -> String -> m (t, t1) | ||
501 | base16decode rs getter s = | ||
502 | either fail (\a -> return (a,rs)) | ||
503 | $ runGet getter | ||
504 | $ fst | ||
505 | $ Base16.decode (C8.pack s) | ||
506 | |||
507 | verifyChecksum :: PublicKey -> Word16 -> Either String () | ||
508 | verifyChecksum _ _ = return () -- TODO | ||
509 | |||
510 | data NoSpamId = NoSpamId NoSpam PublicKey | ||
511 | deriving (Eq,Ord) | ||
512 | |||
513 | |||
514 | nospam64 :: NoSpam -> String | ||
515 | nospam64 (NoSpam w32 Nothing) = n ++ "???" | ||
516 | where n = take 5 $ nospam64 (NoSpam w32 (Just 0)) | ||
517 | nospam64 (NoSpam w32 (Just w16)) = map (nmtoken64 True) $ C8.unpack $ Base64.encode $ runPut $ do | ||
518 | put w32 | ||
519 | put w16 | ||
520 | |||
521 | instance Show NoSpamId where | ||
522 | show (NoSpamId nspam pub) = '$' : nospam64 nspam ++ "@" ++ show (key2id pub) ++ ".tox" | ||
523 | |||
524 | instance Read NoSpamId where | ||
525 | readsPrec d s = either fail id $ do | ||
526 | (jid,xs) <- Right $ break isSpace s | ||
527 | nsid <- parseNoSpamId $ Text.pack jid | ||
528 | return [(nsid,xs)] | ||
529 | |||
530 | parseNoSpamId :: Text -> Either String NoSpamId | ||
531 | parseNoSpamId jid = do | ||
532 | (Just u,h,_) <- Right $ splitJID jid | ||
533 | (base64,".tox") <- Right $ splitAt 43 $ Text.unpack h | ||
534 | pub <- id2key <$> readEither base64 | ||
535 | let ustr = Text.unpack u | ||
536 | '$' : b64digits <- Right ustr -- TODO: support 0x prefix also. | ||
537 | NoSpam nospam (Just x) <- readEither $ map (\case; '?' -> '0'; c -> c) ustr | ||
538 | let nlo = fromIntegral nospam :: Word16 | ||
539 | nhi = fromIntegral (nospam `shiftR` 16) :: Word16 | ||
540 | sum = x `xor` nlo `xor` nhi `xor` xorsum pub | ||
541 | -- Find any question mark indices. | ||
542 | qs = catMaybes $ zipWith (\case; '?' -> Just ; _ -> const Nothing) b64digits [0..7] | ||
543 | -- Break up the /sum/ into a numbered list of two-bit non-zero nibbles. | ||
544 | ns = filter (\case; (_,0) -> False; _ -> True) | ||
545 | $ zip [0..7] | ||
546 | $ unfoldr (\s -> Just (s .&. 0xC000, s `shiftL` 2)) sum | ||
547 | -- Represent the nospam value as a Word64 | ||
548 | n64 = shiftL (fromIntegral nospam) 32 .|. shiftL (fromIntegral x) 16 :: Word64 | ||
549 | |||
550 | -- q=0 1 2 3 4 5 6 7 | ||
551 | -- 012 345 670 123 456 701 234 567 | ||
552 | nibblePlace n q = case mod (n - 3 * q) 8 of | ||
553 | p | p < 3 -> Just (q,p) | ||
554 | _ -> Nothing | ||
555 | |||
556 | solve [] !ac = Right ac | ||
557 | solve ((n,b):ns) !ac = do | ||
558 | -- Find nibble p of question-digit q that corresponds to nibble n. | ||
559 | (q,p) <- maybe (Left "Unsolvable nospam.") Right | ||
560 | $ foldr (<|>) Nothing $ map (nibblePlace n) qs | ||
561 | let bitpos = q * 6 + p * 2 | ||
562 | ac' = ac `xor` shiftR (fromIntegral b `shiftL` 48) bitpos | ||
563 | solve ns ac' | ||
564 | |||
565 | n64' <- solve ns n64 | ||
566 | let nospam' = fromIntegral (n64' `shiftR` 32) | ||
567 | cksum' = fromIntegral (n64' `shiftR` 16) | ||
568 | return $ NoSpamId (NoSpam nospam' (Just cksum')) pub | ||