summaryrefslogtreecommitdiff
path: root/src/Crypto/Tox.hs
diff options
context:
space:
mode:
authorDebian Live user <user@localhost.localdomain>2017-10-28 21:41:08 +0000
committerDebian Live user <user@localhost.localdomain>2017-10-28 21:41:08 +0000
commit225d3f104ce24eb08550ee6cb09d23c184785e59 (patch)
tree8593748f08ad13ab5a4c234eee06973d151d8dbb /src/Crypto/Tox.hs
parente89145df011e7737c59a1ce4568432e2e9291871 (diff)
incrementNonce24, useful for Tox Handshake
Diffstat (limited to 'src/Crypto/Tox.hs')
-rw-r--r--src/Crypto/Tox.hs45
1 files changed, 45 insertions, 0 deletions
diff --git a/src/Crypto/Tox.hs b/src/Crypto/Tox.hs
index 8a65dfb4..9f7c5e16 100644
--- a/src/Crypto/Tox.hs
+++ b/src/Crypto/Tox.hs
@@ -7,6 +7,7 @@
7{-# LANGUAGE DeriveTraversable #-} 7{-# LANGUAGE DeriveTraversable #-}
8{-# LANGUAGE ExplicitNamespaces #-} 8{-# LANGUAGE ExplicitNamespaces #-}
9{-# LANGUAGE TypeOperators #-} 9{-# LANGUAGE TypeOperators #-}
10{-# LANGUAGE MagicHash, UnboxedTuples #-}
10module Crypto.Tox 11module Crypto.Tox
11 ( PublicKey 12 ( PublicKey
12 , publicKey 13 , publicKey
@@ -33,6 +34,7 @@ module Crypto.Tox
33 , decrypt 34 , decrypt
34 , Nonce8(..) 35 , Nonce8(..)
35 , Nonce24(..) 36 , Nonce24(..)
37 , incrementNonce24
36 , Nonce32(..) 38 , Nonce32(..)
37 , getRemainingEncrypted 39 , getRemainingEncrypted
38 , putEncrypted 40 , putEncrypted
@@ -82,6 +84,9 @@ import qualified Data.ByteString.Internal
82import Control.Concurrent.STM 84import Control.Concurrent.STM
83import Crypto.Error.Types (CryptoFailable (..), throwCryptoError) 85import Crypto.Error.Types (CryptoFailable (..), throwCryptoError)
84import Network.Socket (SockAddr) 86import Network.Socket (SockAddr)
87import GHC.Exts (Word(..))
88import GHC.Prim
89import Data.Word64Map (fitsInInt)
85 90
86-- | A 16-byte mac and an arbitrary-length encrypted stream. 91-- | A 16-byte mac and an arbitrary-length encrypted stream.
87newtype Encrypted a = Encrypted ByteString 92newtype Encrypted a = Encrypted ByteString
@@ -253,6 +258,46 @@ hsalsa20 k n = BA.append a b
253newtype Nonce24 = Nonce24 ByteString 258newtype Nonce24 = Nonce24 ByteString
254 deriving (Eq, Ord, ByteArrayAccess,Data) 259 deriving (Eq, Ord, ByteArrayAccess,Data)
255 260
261incrementNonce24 :: Nonce24 -> IO Nonce24
262incrementNonce24 (Nonce24 n24) = Nonce24 <$> BA.copy n24 init
263 where
264 init :: Ptr Word -> IO ()
265 init ptr | fitsInInt (Proxy :: Proxy Word64) = do
266 let frmBE64 = fromIntegral . fromBE64 . fromIntegral
267 tBE64 = fromIntegral . toBE64 . fromIntegral
268 W# w1 <- frmBE64 <$> peek ptr
269 W# w2 <- frmBE64 <$> peekElemOff ptr 1
270 W# w3 <- frmBE64 <$> peekElemOff ptr 2
271 let (# overflw, sum #) = plusWord2# w3 (int2Word# 1#)
272 (# overflw', sum' #) = plusWord2# w2 overflw
273 (# discard, sum'' #) = plusWord2# w1 overflw'
274 poke ptr $ tBE64 (W# sum'')
275 pokeElemOff ptr 1 $ tBE64 (W# sum')
276 pokeElemOff ptr 2 $ tBE64 (W# sum)
277
278 init ptr | fitsInInt (Proxy :: Proxy Word32) = do
279 let frmBE32 = fromIntegral . fromBE32 . fromIntegral
280 tBE32 = fromIntegral . toBE32 . fromIntegral
281 W# w1 <- frmBE32 <$> peek ptr
282 W# w2 <- frmBE32 <$> peekElemOff ptr 1
283 W# w3 <- frmBE32 <$> peekElemOff ptr 2
284 W# w4 <- frmBE32 <$> peekElemOff ptr 3
285 W# w5 <- frmBE32 <$> peekElemOff ptr 4
286 W# w6 <- frmBE32 <$> peekElemOff ptr 5
287 let (# overflw_, sum_ #) = plusWord2# w6 (int2Word# 1#)
288 (# overflw__, sum__ #) = plusWord2# w5 overflw_
289 (# overflw___, sum___ #) = plusWord2# w6 overflw__
290 (# overflw, sum #) = plusWord2# w3 overflw___
291 (# overflw', sum' #) = plusWord2# w2 overflw
292 (# discard, sum'' #) = plusWord2# w1 overflw'
293 poke ptr $ tBE32 (W# sum'')
294 pokeElemOff ptr 1 $ tBE32 (W# sum')
295 pokeElemOff ptr 2 $ tBE32 (W# sum)
296 pokeElemOff ptr 3 $ tBE32 (W# sum___)
297 pokeElemOff ptr 4 $ tBE32 (W# sum__)
298 pokeElemOff ptr 5 $ tBE32 (W# sum_)
299 init _ = error "incrementNonce24: I only support 64 and 32 bits"
300
256quoted :: ShowS -> ShowS 301quoted :: ShowS -> ShowS
257quoted shows s = '"':shows ('"':s) 302quoted shows s = '"':shows ('"':s)
258 303