{-# LANGUAGE TypeFamilies #-}
{-# LANGUAGE TypeOperators #-}
module NaCl.Stream
( Key
, toKey
, Nonce
, toNonce
, MaxStreamSize
, generate
, xor
) where
import Data.ByteArray (ByteArray, ByteArrayAccess)
import Data.ByteArray.Sized (ByteArrayN)
import GHC.TypeLits (type (<=))
import System.IO.Unsafe (unsafePerformIO)
import NaCl.Stream.Internal (Nonce, Key, MaxStreamSize, toNonce, toKey)
import qualified NaCl.Stream.Internal as I
generate
:: forall n key nonce ct.
( ByteArrayAccess key, ByteArrayAccess nonce
, ByteArrayN n ct
, n <= MaxStreamSize
)
=> Key key
-> Nonce nonce
-> ct
generate :: Key key -> Nonce nonce -> ct
generate Key key
key Nonce nonce
nonce =
IO ct -> ct
forall a. IO a -> a
unsafePerformIO (IO ct -> ct) -> IO ct -> ct
forall a b. (a -> b) -> a -> b
$ Key key -> Nonce nonce -> IO ct
forall key nonce (n :: Nat) ct.
(ByteArrayAccess key, ByteArrayAccess nonce, ByteArrayN n ct,
n <= MaxStreamSize) =>
Key key -> Nonce nonce -> IO ct
I.generate Key key
key Nonce nonce
nonce
xor
:: ( ByteArrayAccess key, ByteArrayAccess nonce
, ByteArrayAccess pt, ByteArray ct
)
=> Key key
-> Nonce nonce
-> pt
-> ct
xor :: Key key -> Nonce nonce -> pt -> ct
xor Key key
key Nonce nonce
nonce pt
msg =
IO ct -> ct
forall a. IO a -> a
unsafePerformIO (IO ct -> ct) -> IO ct -> ct
forall a b. (a -> b) -> a -> b
$ Key key -> Nonce nonce -> pt -> IO ct
forall key nonce pt ct.
(ByteArrayAccess key, ByteArrayAccess nonce, ByteArrayAccess pt,
ByteArray ct) =>
Key key -> Nonce nonce -> pt -> IO ct
I.xor Key key
key Nonce nonce
nonce pt
msg