{-# LANGUAGE DeriveDataTypeable, GeneralizedNewtypeDeriving, DeriveGeneric #-}

-- |
-- Module      : Crypto.Saltine.Core.Stream
-- Copyright   : (c) Joseph Abrahamson 2013
-- License     : MIT
--
-- Maintainer  : me@jspha.com
-- Stability   : experimental
-- Portability : non-portable
--
-- Secret-key encryption:
-- "Crypto.Saltine.Core.Stream"
--
-- The 'stream' function produces a sized stream 'ByteString' as a
-- function of a secret key and a nonce. The 'xor' function encrypts a
-- message 'ByteString' using a secret key and a nonce.  The 'xor'
-- function guarantees that the ciphertext has the same length as the
-- plaintext, and is the @plaintext `xor` stream k n@. Consequently
-- 'xor' can also be used to decrypt.
--
-- The 'stream' function, viewed as a function of the nonce for a
-- uniform random key, is designed to meet the standard notion of
-- unpredictability (\"PRF\"). For a formal definition see, e.g.,
-- Section 2.3 of Bellare, Kilian, and Rogaway, \"The security of the
-- cipher block chaining message authentication code,\" Journal of
-- Computer and System Sciences 61 (2000), 362–399;
-- <http://www-cse.ucsd.edu/~mihir/papers/cbc.html>. This means that
-- an attacker cannot distinguish this function from a uniform random
-- function. Consequently, if a series of messages is encrypted by
-- 'xor' with /a different nonce for each message/, the ciphertexts
-- are indistinguishable from uniform random strings of the same
-- length.
--
-- Note that the length is not hidden. Note also that it is the
-- caller's responsibility to ensure the uniqueness of nonces—for
-- example, by using nonce 1 for the first message, nonce 2 for the
-- second message, etc. Nonces are long enough that randomly generated
-- nonces have negligible risk of collision.
--
-- Saltine does not make any promises regarding the resistance of
-- crypto_stream to \"related-key attacks.\" It is the caller's
-- responsibility to use proper key-derivation functions.
--
-- "Crypto.Saltine.Core.Stream" is @crypto_stream_xsalsa20@, a
-- particular cipher specified in \"Cryptography in NaCl\"
-- (<http://nacl.cr.yp.to/valid.html>), Section 7. This cipher is
-- conjectured to meet the standard notion of unpredictability.
--
-- This is version 2010.08.30 of the stream.html web page.

module Crypto.Saltine.Core.Stream (
  Key, Nonce,
  newKey, newNonce,
  stream, xor
  ) where

import           Crypto.Saltine.Class
import           Crypto.Saltine.Internal.Util
import qualified Crypto.Saltine.Internal.ByteSizes as Bytes

import           Control.Applicative
import           Foreign.C
import           Foreign.Ptr
import qualified Data.ByteString as S
import           Data.ByteString (ByteString)
import           Data.Hashable (Hashable)
import           Data.Data (Data, Typeable)
import           GHC.Generics (Generic)

-- $types

-- | An opaque 'stream' cryptographic key.
newtype Key = Key ByteString deriving (Key -> Key -> Bool
(Key -> Key -> Bool) -> (Key -> Key -> Bool) -> Eq Key
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Key -> Key -> Bool
$c/= :: Key -> Key -> Bool
== :: Key -> Key -> Bool
$c== :: Key -> Key -> Bool
Eq, Eq Key
Eq Key =>
(Key -> Key -> Ordering)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Bool)
-> (Key -> Key -> Key)
-> (Key -> Key -> Key)
-> Ord Key
Key -> Key -> Bool
Key -> Key -> Ordering
Key -> Key -> Key
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Key -> Key -> Key
$cmin :: Key -> Key -> Key
max :: Key -> Key -> Key
$cmax :: Key -> Key -> Key
>= :: Key -> Key -> Bool
$c>= :: Key -> Key -> Bool
> :: Key -> Key -> Bool
$c> :: Key -> Key -> Bool
<= :: Key -> Key -> Bool
$c<= :: Key -> Key -> Bool
< :: Key -> Key -> Bool
$c< :: Key -> Key -> Bool
compare :: Key -> Key -> Ordering
$ccompare :: Key -> Key -> Ordering
$cp1Ord :: Eq Key
Ord, Int -> Key -> Int
Key -> Int
(Int -> Key -> Int) -> (Key -> Int) -> Hashable Key
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Key -> Int
$chash :: Key -> Int
hashWithSalt :: Int -> Key -> Int
$chashWithSalt :: Int -> Key -> Int
Hashable, Typeable Key
DataType
Constr
Typeable Key =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Key -> c Key)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Key)
-> (Key -> Constr)
-> (Key -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Key))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key))
-> ((forall b. Data b => b -> b) -> Key -> Key)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r)
-> (forall u. (forall d. Data d => d -> u) -> Key -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Key -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Key -> m Key)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Key -> m Key)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Key -> m Key)
-> Data Key
Key -> DataType
Key -> Constr
(forall b. Data b => b -> b) -> Key -> Key
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Key -> c Key
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Key
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Key -> u
forall u. (forall d. Data d => d -> u) -> Key -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Key -> m Key
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Key -> m Key
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Key
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Key -> c Key
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Key)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key)
$cKey :: Constr
$tKey :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Key -> m Key
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Key -> m Key
gmapMp :: (forall d. Data d => d -> m d) -> Key -> m Key
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Key -> m Key
gmapM :: (forall d. Data d => d -> m d) -> Key -> m Key
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Key -> m Key
gmapQi :: Int -> (forall d. Data d => d -> u) -> Key -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Key -> u
gmapQ :: (forall d. Data d => d -> u) -> Key -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Key -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Key -> r
gmapT :: (forall b. Data b => b -> b) -> Key -> Key
$cgmapT :: (forall b. Data b => b -> b) -> Key -> Key
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Key)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Key)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Key)
dataTypeOf :: Key -> DataType
$cdataTypeOf :: Key -> DataType
toConstr :: Key -> Constr
$ctoConstr :: Key -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Key
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Key
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Key -> c Key
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Key -> c Key
$cp1Data :: Typeable Key
Data, Typeable, (forall x. Key -> Rep Key x)
-> (forall x. Rep Key x -> Key) -> Generic Key
forall x. Rep Key x -> Key
forall x. Key -> Rep Key x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Key x -> Key
$cfrom :: forall x. Key -> Rep Key x
Generic)

instance IsEncoding Key where
  decode :: ByteString -> Maybe Key
decode v :: ByteString
v = if ByteString -> Int
S.length ByteString
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
Bytes.streamKey
           then Key -> Maybe Key
forall a. a -> Maybe a
Just (ByteString -> Key
Key ByteString
v)
           else Maybe Key
forall a. Maybe a
Nothing
  {-# INLINE decode #-}
  encode :: Key -> ByteString
encode (Key v :: ByteString
v) = ByteString
v
  {-# INLINE encode #-}

-- | An opaque 'stream' nonce.
newtype Nonce = Nonce ByteString deriving (Nonce -> Nonce -> Bool
(Nonce -> Nonce -> Bool) -> (Nonce -> Nonce -> Bool) -> Eq Nonce
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: Nonce -> Nonce -> Bool
$c/= :: Nonce -> Nonce -> Bool
== :: Nonce -> Nonce -> Bool
$c== :: Nonce -> Nonce -> Bool
Eq, Eq Nonce
Eq Nonce =>
(Nonce -> Nonce -> Ordering)
-> (Nonce -> Nonce -> Bool)
-> (Nonce -> Nonce -> Bool)
-> (Nonce -> Nonce -> Bool)
-> (Nonce -> Nonce -> Bool)
-> (Nonce -> Nonce -> Nonce)
-> (Nonce -> Nonce -> Nonce)
-> Ord Nonce
Nonce -> Nonce -> Bool
Nonce -> Nonce -> Ordering
Nonce -> Nonce -> Nonce
forall a.
Eq a =>
(a -> a -> Ordering)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> Bool)
-> (a -> a -> a)
-> (a -> a -> a)
-> Ord a
min :: Nonce -> Nonce -> Nonce
$cmin :: Nonce -> Nonce -> Nonce
max :: Nonce -> Nonce -> Nonce
$cmax :: Nonce -> Nonce -> Nonce
>= :: Nonce -> Nonce -> Bool
$c>= :: Nonce -> Nonce -> Bool
> :: Nonce -> Nonce -> Bool
$c> :: Nonce -> Nonce -> Bool
<= :: Nonce -> Nonce -> Bool
$c<= :: Nonce -> Nonce -> Bool
< :: Nonce -> Nonce -> Bool
$c< :: Nonce -> Nonce -> Bool
compare :: Nonce -> Nonce -> Ordering
$ccompare :: Nonce -> Nonce -> Ordering
$cp1Ord :: Eq Nonce
Ord, Int -> Nonce -> Int
Nonce -> Int
(Int -> Nonce -> Int) -> (Nonce -> Int) -> Hashable Nonce
forall a. (Int -> a -> Int) -> (a -> Int) -> Hashable a
hash :: Nonce -> Int
$chash :: Nonce -> Int
hashWithSalt :: Int -> Nonce -> Int
$chashWithSalt :: Int -> Nonce -> Int
Hashable, Typeable Nonce
DataType
Constr
Typeable Nonce =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> Nonce -> c Nonce)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c Nonce)
-> (Nonce -> Constr)
-> (Nonce -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c Nonce))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Nonce))
-> ((forall b. Data b => b -> b) -> Nonce -> Nonce)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Nonce -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Nonce -> r)
-> (forall u. (forall d. Data d => d -> u) -> Nonce -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> Nonce -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> Nonce -> m Nonce)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Nonce -> m Nonce)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> Nonce -> m Nonce)
-> Data Nonce
Nonce -> DataType
Nonce -> Constr
(forall b. Data b => b -> b) -> Nonce -> Nonce
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Nonce -> c Nonce
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Nonce
forall a.
Typeable a =>
(forall (c :: * -> *).
 (forall d b. Data d => c (d -> b) -> d -> c b)
 -> (forall g. g -> c g) -> a -> c a)
-> (forall (c :: * -> *).
    (forall b r. Data b => c (b -> r) -> c r)
    -> (forall r. r -> c r) -> Constr -> c a)
-> (a -> Constr)
-> (a -> DataType)
-> (forall (t :: * -> *) (c :: * -> *).
    Typeable t =>
    (forall d. Data d => c (t d)) -> Maybe (c a))
-> (forall (t :: * -> * -> *) (c :: * -> *).
    Typeable t =>
    (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c a))
-> ((forall b. Data b => b -> b) -> a -> a)
-> (forall r r'.
    (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall r r'.
    (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> a -> r)
-> (forall u. (forall d. Data d => d -> u) -> a -> [u])
-> (forall u. Int -> (forall d. Data d => d -> u) -> a -> u)
-> (forall (m :: * -> *).
    Monad m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> (forall (m :: * -> *).
    MonadPlus m =>
    (forall d. Data d => d -> m d) -> a -> m a)
-> Data a
forall u. Int -> (forall d. Data d => d -> u) -> Nonce -> u
forall u. (forall d. Data d => d -> u) -> Nonce -> [u]
forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Nonce -> r
forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Nonce -> r
forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Nonce -> m Nonce
forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Nonce -> m Nonce
forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Nonce
forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Nonce -> c Nonce
forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Nonce)
forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Nonce)
$cNonce :: Constr
$tNonce :: DataType
gmapMo :: (forall d. Data d => d -> m d) -> Nonce -> m Nonce
$cgmapMo :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Nonce -> m Nonce
gmapMp :: (forall d. Data d => d -> m d) -> Nonce -> m Nonce
$cgmapMp :: forall (m :: * -> *).
MonadPlus m =>
(forall d. Data d => d -> m d) -> Nonce -> m Nonce
gmapM :: (forall d. Data d => d -> m d) -> Nonce -> m Nonce
$cgmapM :: forall (m :: * -> *).
Monad m =>
(forall d. Data d => d -> m d) -> Nonce -> m Nonce
gmapQi :: Int -> (forall d. Data d => d -> u) -> Nonce -> u
$cgmapQi :: forall u. Int -> (forall d. Data d => d -> u) -> Nonce -> u
gmapQ :: (forall d. Data d => d -> u) -> Nonce -> [u]
$cgmapQ :: forall u. (forall d. Data d => d -> u) -> Nonce -> [u]
gmapQr :: (r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Nonce -> r
$cgmapQr :: forall r r'.
(r' -> r -> r) -> r -> (forall d. Data d => d -> r') -> Nonce -> r
gmapQl :: (r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Nonce -> r
$cgmapQl :: forall r r'.
(r -> r' -> r) -> r -> (forall d. Data d => d -> r') -> Nonce -> r
gmapT :: (forall b. Data b => b -> b) -> Nonce -> Nonce
$cgmapT :: (forall b. Data b => b -> b) -> Nonce -> Nonce
dataCast2 :: (forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Nonce)
$cdataCast2 :: forall (t :: * -> * -> *) (c :: * -> *).
Typeable t =>
(forall d e. (Data d, Data e) => c (t d e)) -> Maybe (c Nonce)
dataCast1 :: (forall d. Data d => c (t d)) -> Maybe (c Nonce)
$cdataCast1 :: forall (t :: * -> *) (c :: * -> *).
Typeable t =>
(forall d. Data d => c (t d)) -> Maybe (c Nonce)
dataTypeOf :: Nonce -> DataType
$cdataTypeOf :: Nonce -> DataType
toConstr :: Nonce -> Constr
$ctoConstr :: Nonce -> Constr
gunfold :: (forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Nonce
$cgunfold :: forall (c :: * -> *).
(forall b r. Data b => c (b -> r) -> c r)
-> (forall r. r -> c r) -> Constr -> c Nonce
gfoldl :: (forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Nonce -> c Nonce
$cgfoldl :: forall (c :: * -> *).
(forall d b. Data d => c (d -> b) -> d -> c b)
-> (forall g. g -> c g) -> Nonce -> c Nonce
$cp1Data :: Typeable Nonce
Data, Typeable, (forall x. Nonce -> Rep Nonce x)
-> (forall x. Rep Nonce x -> Nonce) -> Generic Nonce
forall x. Rep Nonce x -> Nonce
forall x. Nonce -> Rep Nonce x
forall a.
(forall x. a -> Rep a x) -> (forall x. Rep a x -> a) -> Generic a
$cto :: forall x. Rep Nonce x -> Nonce
$cfrom :: forall x. Nonce -> Rep Nonce x
Generic)

instance IsNonce Nonce where
  zero :: Nonce
zero = ByteString -> Nonce
Nonce (Int -> Word8 -> ByteString
S.replicate Int
Bytes.streamNonce 0)
  nudge :: Nonce -> Nonce
nudge (Nonce n :: ByteString
n) = ByteString -> Nonce
Nonce (ByteString -> ByteString
nudgeBS ByteString
n)

instance IsEncoding Nonce where
  decode :: ByteString -> Maybe Nonce
decode v :: ByteString
v = if ByteString -> Int
S.length ByteString
v Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
== Int
Bytes.streamNonce
           then Nonce -> Maybe Nonce
forall a. a -> Maybe a
Just (ByteString -> Nonce
Nonce ByteString
v)
           else Maybe Nonce
forall a. Maybe a
Nothing
  {-# INLINE decode #-}
  encode :: Nonce -> ByteString
encode (Nonce v :: ByteString
v) = ByteString
v
  {-# INLINE encode #-}

-- | Creates a random key of the correct size for 'stream' and 'xor'.
newKey :: IO Key
newKey :: IO Key
newKey = ByteString -> Key
Key (ByteString -> Key) -> IO ByteString -> IO Key
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> IO ByteString
randomByteString Int
Bytes.streamKey

-- | Creates a random nonce of the correct size for 'stream' and
-- 'xor'.
newNonce :: IO Nonce
newNonce :: IO Nonce
newNonce = ByteString -> Nonce
Nonce (ByteString -> Nonce) -> IO ByteString -> IO Nonce
forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> Int -> IO ByteString
randomByteString Int
Bytes.streamNonce

-- | Generates a cryptographic random stream indexed by the 'Key' and
-- 'Nonce'. These streams are indistinguishable from random noise so
-- long as the 'Nonce' is not used more than once.
stream :: Key -> Nonce -> Int
       -> ByteString
       -- ^ Cryptographic stream
stream :: Key -> Nonce -> Int -> ByteString
stream (Key key :: ByteString
key) (Nonce nonce :: ByteString
nonce) n :: Int
n =
  (CInt, ByteString) -> ByteString
forall a b. (a, b) -> b
snd ((CInt, ByteString) -> ByteString)
-> ((Ptr CChar -> IO CInt) -> (CInt, ByteString))
-> (Ptr CChar -> IO CInt)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> (Ptr CChar -> IO CInt) -> (CInt, ByteString)
forall b. Int -> (Ptr CChar -> IO b) -> (b, ByteString)
buildUnsafeByteString Int
n ((Ptr CChar -> IO CInt) -> ByteString)
-> (Ptr CChar -> IO CInt) -> ByteString
forall a b. (a -> b) -> a -> b
$ \ps :: Ptr CChar
ps ->
    [ByteString] -> ([CStringLen] -> IO CInt) -> IO CInt
forall b. [ByteString] -> ([CStringLen] -> IO b) -> IO b
constByteStrings [ByteString
key, ByteString
nonce] (([CStringLen] -> IO CInt) -> IO CInt)
-> ([CStringLen] -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \[(pk :: Ptr CChar
pk, _), (pn :: Ptr CChar
pn, _)] ->
    Ptr CChar -> CULLong -> Ptr CChar -> Ptr CChar -> IO CInt
c_stream Ptr CChar
ps (Int -> CULLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
n) Ptr CChar
pn Ptr CChar
pk

-- | Computes the exclusive-or between a message and a cryptographic
-- random stream indexed by the 'Key' and the 'Nonce'. This renders
-- the output indistinguishable from random noise so long as the
-- 'Nonce' is not used more than once. /Note:/ while this can be used
-- for encryption and decryption, it is /possible for an attacker to/
-- /manipulate the message in transit without detection/. USE AT YOUR
-- OWN RISK.
xor :: Key -> Nonce
    -> ByteString
    -- ^ Message
    -> ByteString
    -- ^ Ciphertext
xor :: Key -> Nonce -> ByteString -> ByteString
xor (Key key :: ByteString
key) (Nonce nonce :: ByteString
nonce) msg :: ByteString
msg =
  (CInt, ByteString) -> ByteString
forall a b. (a, b) -> b
snd ((CInt, ByteString) -> ByteString)
-> ((Ptr CChar -> IO CInt) -> (CInt, ByteString))
-> (Ptr CChar -> IO CInt)
-> ByteString
forall b c a. (b -> c) -> (a -> b) -> a -> c
. Int -> (Ptr CChar -> IO CInt) -> (CInt, ByteString)
forall b. Int -> (Ptr CChar -> IO b) -> (b, ByteString)
buildUnsafeByteString Int
len ((Ptr CChar -> IO CInt) -> ByteString)
-> (Ptr CChar -> IO CInt) -> ByteString
forall a b. (a -> b) -> a -> b
$ \pc :: Ptr CChar
pc ->
    [ByteString] -> ([CStringLen] -> IO CInt) -> IO CInt
forall b. [ByteString] -> ([CStringLen] -> IO b) -> IO b
constByteStrings [ByteString
key, ByteString
nonce, ByteString
msg] (([CStringLen] -> IO CInt) -> IO CInt)
-> ([CStringLen] -> IO CInt) -> IO CInt
forall a b. (a -> b) -> a -> b
$ \[(pk :: Ptr CChar
pk, _), (pn :: Ptr CChar
pn, _), (pm :: Ptr CChar
pm, _)] ->
    Ptr CChar
-> Ptr CChar -> CULLong -> Ptr CChar -> Ptr CChar -> IO CInt
c_stream_xor Ptr CChar
pc Ptr CChar
pm (Int -> CULLong
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len) Ptr CChar
pn Ptr CChar
pk
  where len :: Int
len = ByteString -> Int
S.length ByteString
msg

foreign import ccall "crypto_stream"
  c_stream :: Ptr CChar
           -- ^ Stream output buffer
           -> CULLong
           -- ^ Length of stream to generate
           -> Ptr CChar
           -- ^ Constant nonce buffer
           -> Ptr CChar
           -- ^ Constant key buffer
           -> IO CInt
           -- ^ Always 0

foreign import ccall "crypto_stream_xor"
  c_stream_xor :: Ptr CChar
               -- ^ Ciphertext output buffer
               -> Ptr CChar
               -- ^ Constant message buffer
               -> CULLong
               -- ^ Length of message buffer
               -> Ptr CChar
               -- ^ Constant nonce buffer
               -> Ptr CChar
               -- ^ Constant key buffer
               -> IO CInt
               -- ^ Always 0