summaryrefslogtreecommitdiff
diff options
context:
space:
mode:
authorJoe Crayne <joe@jerkface.net>2020-01-09 12:10:10 -0500
committerJoe Crayne <joe@jerkface.net>2020-01-09 12:10:10 -0500
commit5e2f6f9f8b78b90f0becb60e735abbd62bac6ca6 (patch)
tree9d7398a42a2925fe4f7e760e7d5ee9ae0a0a75fe
parentb9194d4637ddfc3b9f762d2e4e29a318087e02db (diff)
Moved Codec.AsciiKey256 to tox-crypto.
-rw-r--r--dht/Presence/Presence.hs3
-rw-r--r--dht/ToxManager.hs1
-rw-r--r--dht/dht-client.cabal3
-rw-r--r--dht/examples/dhtd.hs1
-rw-r--r--dht/src/Data/Tox/Msg.hs4
-rw-r--r--dht/src/DebugTag.hs1
-rw-r--r--dht/src/Network/Tox/NodeId.hs8
-rw-r--r--tox-crypto/cbits/crc4_itu.c (renamed from dht/cbits/crc4_itu.c)0
-rw-r--r--tox-crypto/src/Codec/AsciiKey256.hs (renamed from dht/src/Codec/AsciiKey256.hs)31
-rw-r--r--tox-crypto/src/Crypto/Tox.hs11
-rw-r--r--tox-crypto/tox-crypto.cabal5
11 files changed, 40 insertions, 28 deletions
diff --git a/dht/Presence/Presence.hs b/dht/Presence/Presence.hs
index b8c9f923..866aad78 100644
--- a/dht/Presence/Presence.hs
+++ b/dht/Presence/Presence.hs
@@ -51,10 +51,9 @@ import Util
51import qualified Connection 51import qualified Connection
52 ;import Connection (PeerAddress (..), resolvePeer, reverseAddress) 52 ;import Connection (PeerAddress (..), resolvePeer, reverseAddress)
53import Network.Tox.NodeId (key2id,parseNoSpamId,nospam64,NoSpamId(..),ToxProgress,ToxContact(..)) 53import Network.Tox.NodeId (key2id,parseNoSpamId,nospam64,NoSpamId(..),ToxProgress,ToxContact(..))
54import Crypto.Tox (decodeSecret,encodeSecret, generateSecretKey) 54import Crypto.Tox (decodeSecret,encodeSecret, generateSecretKey, stripSuffix)
55import DPut 55import DPut
56import DebugTag 56import DebugTag
57import Codec.AsciiKey256
58 57
59{- 58{-
60isPeerKey :: ClientAddress -> Bool 59isPeerKey :: ClientAddress -> Bool
diff --git a/dht/ToxManager.hs b/dht/ToxManager.hs
index f5a8fd15..4c67e853 100644
--- a/dht/ToxManager.hs
+++ b/dht/ToxManager.hs
@@ -9,7 +9,6 @@ module ToxManager where
9import Announcer 9import Announcer
10import Announcer.Tox 10import Announcer.Tox
11import ClientState 11import ClientState
12import Codec.AsciiKey256
13import ConfigFiles 12import ConfigFiles
14import Control.Arrow 13import Control.Arrow
15import Control.Concurrent.STM 14import Control.Concurrent.STM
diff --git a/dht/dht-client.cabal b/dht/dht-client.cabal
index 362f4b36..79a72c05 100644
--- a/dht/dht-client.cabal
+++ b/dht/dht-client.cabal
@@ -153,7 +153,6 @@ library
153 Network.Tox.AggregateSession 153 Network.Tox.AggregateSession
154 Network.Tox.Session 154 Network.Tox.Session
155 DebugTag 155 DebugTag
156 Codec.AsciiKey256
157 Paths_dht_client 156 Paths_dht_client
158 157
159 build-depends: base 158 build-depends: base
@@ -252,7 +251,7 @@ library
252 251
253 252
254 253
255 C-sources: Presence/monitortty.c cbits/crc4_itu.c 254 C-sources: Presence/monitortty.c
256 255
257 -- if flag(aeson) 256 -- if flag(aeson)
258 build-depends: aeson, aeson-pretty, unordered-containers, vector 257 build-depends: aeson, aeson-pretty, unordered-containers, vector
diff --git a/dht/examples/dhtd.hs b/dht/examples/dhtd.hs
index 3078831d..2f39303c 100644
--- a/dht/examples/dhtd.hs
+++ b/dht/examples/dhtd.hs
@@ -66,7 +66,6 @@ import System.Posix.Signals
66import Announcer 66import Announcer
67import Announcer.Tox 67import Announcer.Tox
68import ToxManager 68import ToxManager
69import Codec.AsciiKey256
70import Crypto.Tox -- (zeros32,SecretKey,PublicKey, generateSecretKey, toPublic, encodeSecret, decodeSecret, userKeys) 69import Crypto.Tox -- (zeros32,SecretKey,PublicKey, generateSecretKey, toPublic, encodeSecret, decodeSecret, userKeys)
71import qualified Data.Tox.DHT.Multi as Multi 70import qualified Data.Tox.DHT.Multi as Multi
72import DebugUtil 71import DebugUtil
diff --git a/dht/src/Data/Tox/Msg.hs b/dht/src/Data/Tox/Msg.hs
index 4398586f..3188d86f 100644
--- a/dht/src/Data/Tox/Msg.hs
+++ b/dht/src/Data/Tox/Msg.hs
@@ -259,13 +259,13 @@ instance Serialize ChatID where
259 259
260instance Read ChatID where 260instance Read ChatID where
261 readsPrec _ s 261 readsPrec _ s
262 | Right bs <- parseToken32 s 262 | Right bs <- parseBase64Key256 s
263 , CryptoPassed ed <- Ed25519.publicKey bs 263 , CryptoPassed ed <- Ed25519.publicKey bs
264 = [ (ChatID ed, Prelude.drop 43 s) ] 264 = [ (ChatID ed, Prelude.drop 43 s) ]
265 | otherwise = [] 265 | otherwise = []
266 266
267instance Show ChatID where 267instance Show ChatID where
268 show (ChatID ed) = showToken32 ed 268 show (ChatID ed) = showBase64Key256 ed
269 269
270data InviteType = GroupInvite { groupName :: Text } 270data InviteType = GroupInvite { groupName :: Text }
271 | AcceptedInvite 271 | AcceptedInvite
diff --git a/dht/src/DebugTag.hs b/dht/src/DebugTag.hs
index 9ac04bb0..efa6415f 100644
--- a/dht/src/DebugTag.hs
+++ b/dht/src/DebugTag.hs
@@ -12,6 +12,7 @@ data DebugTag
12 | XNetCrypto 12 | XNetCrypto
13 | XNetCryptoOut 13 | XNetCryptoOut
14 | XOnion 14 | XOnion
15 | XRelay
15 | XRoutes 16 | XRoutes
16 | XPing 17 | XPing
17 | XRefresh 18 | XRefresh
diff --git a/dht/src/Network/Tox/NodeId.hs b/dht/src/Network/Tox/NodeId.hs
index 667e7d71..3a2a4f07 100644
--- a/dht/src/Network/Tox/NodeId.hs
+++ b/dht/src/Network/Tox/NodeId.hs
@@ -37,9 +37,8 @@ module Network.Tox.NodeId
37 , verifyChecksum 37 , verifyChecksum
38 , ToxContact(..) 38 , ToxContact(..)
39 , ToxProgress(..) 39 , ToxProgress(..)
40 , parseToken32 40 , showBase64Key256
41 , showToken32 41 , showBase32Key256
42 , show32Token32
43 , nodeInfoFromJSON 42 , nodeInfoFromJSON
44 , showHexId 43 , showHexId
45 ) where 44 ) where
@@ -97,7 +96,6 @@ import System.Endian
97import qualified Data.Text as Text 96import qualified Data.Text as Text
98 ;import Data.Text (Text) 97 ;import Data.Text (Text)
99import Util (splitJID) 98import Util (splitJID)
100import Codec.AsciiKey256
101 99
102-- | perform io for hashes that do allocation and ffi. 100-- | perform io for hashes that do allocation and ffi.
103-- unsafeDupablePerformIO is used when possible as the 101-- unsafeDupablePerformIO is used when possible as the
@@ -174,7 +172,7 @@ instance Read NodeId where
174 readsPrec _ str = readsPrecKey256 (fmap key2id . maybeCryptoError . publicKey) str 172 readsPrec _ str = readsPrecKey256 (fmap key2id . maybeCryptoError . publicKey) str
175 173
176instance Show NodeId where 174instance Show NodeId where
177 show nid = show32Token32 $ id2key nid 175 show nid = showBase32Key256 $ id2key nid
178 176
179instance S.Serialize NodeId where 177instance S.Serialize NodeId where
180 get = key2id <$> getPublicKey 178 get = key2id <$> getPublicKey
diff --git a/dht/cbits/crc4_itu.c b/tox-crypto/cbits/crc4_itu.c
index 8e3b0489..8e3b0489 100644
--- a/dht/cbits/crc4_itu.c
+++ b/tox-crypto/cbits/crc4_itu.c
diff --git a/dht/src/Codec/AsciiKey256.hs b/tox-crypto/src/Codec/AsciiKey256.hs
index 1738a368..0212d1d0 100644
--- a/dht/src/Codec/AsciiKey256.hs
+++ b/tox-crypto/src/Codec/AsciiKey256.hs
@@ -63,12 +63,12 @@ zb32digit c = or [ '3' <= c && c <= '9'
63 63
64 64
65-- | Parse 43-digit base64 token into 32-byte bytestring. 65-- | Parse 43-digit base64 token into 32-byte bytestring.
66parseToken32 :: String -> Either String ByteString 66parseBase64Key256 :: String -> Either String ByteString
67parseToken32 str = fmap (BA.drop 1) $ Base64.decode $ C8.pack $ 'A':map (nmtoken64 False) (take 43 str) 67parseBase64Key256 str = fmap (BA.drop 1) $ Base64.decode $ C8.pack $ 'A':map (nmtoken64 False) (take 43 str)
68 68
69-- | Encode 43-digit base64 token from 32-byte bytestring. 69-- | Encode 43-digit base64 token from 32-byte bytestring.
70showToken32 :: ByteArrayAccess bin => bin -> String 70showBase64Key256 :: ByteArrayAccess bin => bin -> String
71showToken32 bs = map (nmtoken64 True) $ C8.unpack $ BA.drop 1 $ Base64.encode $ BA.cons 0 $ BA.convert bs 71showBase64Key256 bs = map (nmtoken64 True) $ C8.unpack $ BA.drop 1 $ Base64.encode $ BA.cons 0 $ BA.convert bs
72 72
73foreign import ccall "crc4itu" c_crc4itu :: Word8 -- ^ init crc 73foreign import ccall "crc4itu" c_crc4itu :: Word8 -- ^ init crc
74 -> Ptr Word8 -- ^ data to checksum 74 -> Ptr Word8 -- ^ data to checksum
@@ -83,8 +83,8 @@ crc4itu crc0 b = unsafePerformIO $ BA.withByteArray b $ \p ->
83 c_crc4itu crc0 p (fromIntegral $ BA.length b) 83 c_crc4itu crc0 p (fromIntegral $ BA.length b)
84 84
85-- | Parse 52-digit z-base32 token into 32-byte bytestring. 85-- | Parse 52-digit z-base32 token into 32-byte bytestring.
86parse32Token32 :: String -> Either String ByteString 86parseBase32Key256 :: String -> Either String ByteString
87parse32Token32 str = do 87parseBase32Key256 str = do
88 bs <- Base32.decode $ C8.pack $ map (fixupDigit32 . toLower) (take 52 str) ++ "y" 88 bs <- Base32.decode $ C8.pack $ map (fixupDigit32 . toLower) (take 52 str) ++ "y"
89 case BA.splitAt 32 bs of 89 case BA.splitAt 32 bs of
90 (key,mac) | crc4itu 0 key == shiftR (BA.index mac 0) 4 90 (key,mac) | crc4itu 0 key == shiftR (BA.index mac 0) 4
@@ -92,22 +92,25 @@ parse32Token32 str = do
92 _ -> Left "Failed cyclic redundancy check." 92 _ -> Left "Failed cyclic redundancy check."
93 93
94-- | Encode 52-digit z-base32 token from 32-byte bytestring. 94-- | Encode 52-digit z-base32 token from 32-byte bytestring.
95show32Token32 :: ByteArrayAccess bin => bin -> String 95showBase32Key256 :: ByteArrayAccess bin => bin -> String
96show32Token32 bs = C8.unpack $ B.take 52 $ Base32.encode (b `B.snoc` shiftL crc 4) 96showBase32Key256 bs = C8.unpack $ B.take 52 $ Base32.encode (b `B.snoc` shiftL crc 4)
97 where 97 where
98 b = BA.convert bs 98 b = BA.convert bs
99 crc = crc4itu 0 bs 99 crc = crc4itu 0 bs
100 100
101-- | Encode 32-byte bytestring for display.
102showKey256 :: ByteArrayAccess bin => bin -> String
103showKey256 = showBase32Key256
101 104
102readsPrecKey256 :: (ByteString -> Maybe a) -> [Char] -> [(a, [Char])] 105readsPrecKey256 :: (ByteString -> Maybe a) -> [Char] -> [(a, [Char])]
103readsPrecKey256 publicKey str 106readsPrecKey256 publicKey str
104 | (bs,_) <- Base16.decode (C8.pack $ take 64 str) 107 | (bs,_) <- Base16.decode (C8.pack $ take 64 str)
105 , Just pub <- publicKey bs 108 , Just pub <- publicKey bs
106 = [ (pub, drop (2 * B.length bs) str) ] 109 = [ (pub, drop (2 * B.length bs) str) ]
107 | Right bs <- parse32Token32 str 110 | Right bs <- parseBase32Key256 str
108 , Just pub <- publicKey bs 111 , Just pub <- publicKey bs
109 = [ (pub, drop 52 str) ] 112 = [ (pub, drop 52 str) ]
110 | Right bs <- parseToken32 str 113 | Right bs <- parseBase64Key256 str
111 , Just pub <- publicKey bs 114 , Just pub <- publicKey bs
112 = [ (pub, drop 43 str) ] 115 = [ (pub, drop 43 str) ]
113 | otherwise = [] 116 | otherwise = []
@@ -118,8 +121,8 @@ parseKey256 nidstr = do
118 let nidbs = C8.pack nidstr 121 let nidbs = C8.pack nidstr
119 (bs,_) = Base16.decode nidbs 122 (bs,_) = Base16.decode nidbs
120 enid = case C8.length nidbs of 123 enid = case C8.length nidbs of
121 52 -> parse32Token32 nidstr 124 52 -> parseBase32Key256 nidstr
122 43 -> parseToken32 nidstr 125 43 -> parseBase64Key256 nidstr
123 _ -> Left "Wrong size of key." 126 _ -> Left "Wrong size of key."
124 idbs <- (guard (B.length bs == 32) >> return bs) 127 idbs <- (guard (B.length bs == 32) >> return bs)
125 <|> either MF.fail return enid 128 <|> either MF.fail return enid
@@ -134,10 +137,10 @@ readP_key256 = do
134 ] 137 ]
135 let failure = MF.fail "Bad key." 138 let failure = MF.fail "Bad key."
136 case is64 of 139 case is64 of
137 32 -> case parse32Token32 hexhash of 140 32 -> case parseBase32Key256 hexhash of
138 Right bs -> return bs 141 Right bs -> return bs
139 _ -> failure 142 _ -> failure
140 64 -> case parseToken32 hexhash of 143 64 -> case parseBase64Key256 hexhash of
141 Right bs -> return bs 144 Right bs -> return bs
142 _ -> failure 145 _ -> failure
143 16 -> case Base16.decode $ C8.pack hexhash of 146 16 -> case Base16.decode $ C8.pack hexhash of
diff --git a/tox-crypto/src/Crypto/Tox.hs b/tox-crypto/src/Crypto/Tox.hs
index 04b55d94..602ead0a 100644
--- a/tox-crypto/src/Crypto/Tox.hs
+++ b/tox-crypto/src/Crypto/Tox.hs
@@ -67,6 +67,16 @@ module Crypto.Tox
67 , encodeSecret 67 , encodeSecret
68 , decodeSecret 68 , decodeSecret
69 , xorsum 69 , xorsum
70 , Codec.AsciiKey256.showBase32Key256
71 , Codec.AsciiKey256.showBase64Key256
72 , Codec.AsciiKey256.showKey256
73 , Codec.AsciiKey256.parseBase64Key256
74 , Codec.AsciiKey256.parseBase32Key256
75 , Codec.AsciiKey256.parseKey256
76 , Codec.AsciiKey256.readP_key256
77 , Codec.AsciiKey256.readsPrecKey256
78 , Codec.AsciiKey256.stripSuffix
79 , Codec.AsciiKey256.nmtoken64
70 ) where 80 ) where
71 81
72import Control.Arrow 82import Control.Arrow
@@ -99,6 +109,7 @@ import Foreign.Marshal.Alloc
99import Foreign.Ptr 109import Foreign.Ptr
100import Foreign.Storable 110import Foreign.Storable
101import System.Endian 111import System.Endian
112import Codec.AsciiKey256
102import Control.Concurrent.STM 113import Control.Concurrent.STM
103#ifdef CRYPTONITE_BACKPORT 114#ifdef CRYPTONITE_BACKPORT
104import Crypto.ECC.Class 115import Crypto.ECC.Class
diff --git a/tox-crypto/tox-crypto.cabal b/tox-crypto/tox-crypto.cabal
index 678cccd5..370b1a85 100644
--- a/tox-crypto/tox-crypto.cabal
+++ b/tox-crypto/tox-crypto.cabal
@@ -16,8 +16,9 @@ extra-source-files: CHANGELOG.md
16cabal-version: >=1.10 16cabal-version: >=1.10
17 17
18library 18library
19 C-sources: cbits/crc4_itu.c
19 exposed-modules: Crypto.Tox 20 exposed-modules: Crypto.Tox
20 other-modules: DebugTag 21 other-modules: DebugTag, Codec.AsciiKey256
21 other-extensions: CPP 22 other-extensions: CPP
22 , GeneralizedNewtypeDeriving 23 , GeneralizedNewtypeDeriving
23 , ScopedTypeVariables 24 , ScopedTypeVariables
@@ -40,8 +41,10 @@ library
40 base 41 base
41 , cpu 42 , cpu
42 , memory 43 , memory
44 , base32-bytestring
43 , base64-bytestring 45 , base64-bytestring
44 , base16-bytestring 46 , base16-bytestring
47 , text
45 , cereal 48 , cereal
46 , word64-map 49 , word64-map
47 , contravariant 50 , contravariant