module Crypto.Saltine.Core.AEAD (
Key, Nonce,
aead, aeadOpen,
aeadDetached, aeadOpenDetached,
newKey, newNonce
) 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)
newtype Key = Key ByteString deriving (Eq, Ord)
instance IsEncoding Key where
decode v = if S.length v == Bytes.secretBoxKey
then Just (Key v)
else Nothing
{-# INLINE decode #-}
encode (Key v) = v
{-# INLINE encode #-}
newtype Nonce = Nonce ByteString deriving (Eq, Ord)
instance IsEncoding Nonce where
decode v = if S.length v == Bytes.secretBoxNonce
then Just (Nonce v)
else Nothing
{-# INLINE decode #-}
encode (Nonce v) = v
{-# INLINE encode #-}
instance IsNonce Nonce where
zero = Nonce (S.replicate Bytes.secretBoxNonce 0)
nudge (Nonce n) = Nonce (nudgeBS n)
newKey :: IO Key
newKey = Key <$> randomByteString Bytes.secretBoxKey
newNonce :: IO Nonce
newNonce = Nonce <$> randomByteString Bytes.secretBoxNonce
aead :: Key -> Nonce
-> ByteString
-> ByteString
-> ByteString
aead (Key key) (Nonce nonce) msg aad =
snd . buildUnsafeByteString clen $ \pc ->
constByteStrings [key, msg, aad, nonce] $ \
[(pk, _), (pm, _), (pa, _), (pn, _)] ->
c_aead pc nullPtr pm (fromIntegral mlen) pa (fromIntegral alen) nullPtr pn pk
where mlen = S.length msg
alen = S.length aad
clen = mlen + Bytes.aead_xchacha20poly1305_ietf_ABYTES
aeadOpen :: Key -> Nonce
-> ByteString
-> ByteString
-> Maybe ByteString
aeadOpen (Key key) (Nonce nonce) cipher aad =
let (err, vec) = buildUnsafeByteString mlen $ \pm ->
constByteStrings [key, cipher, aad, nonce] $ \
[(pk, _), (pc, _), (pa, _), (pn, _)] ->
c_aead_open pm nullPtr nullPtr pc (fromIntegral clen) pa (fromIntegral alen) pn pk
in hush . handleErrno err $ vec
where clen = S.length cipher
alen = S.length aad
mlen = clen - Bytes.aead_xchacha20poly1305_ietf_ABYTES
aeadDetached :: Key -> Nonce
-> ByteString
-> ByteString
-> (ByteString,ByteString)
aeadDetached (Key key) (Nonce nonce) msg aad =
buildUnsafeByteString clen $ \pc ->
fmap snd . buildUnsafeByteString' tlen $ \pt ->
constByteStrings [key, msg, aad, nonce] $ \
[(pk, _), (pm, _), (pa, _), (pn, _)] ->
c_aead_detached pc pt nullPtr pm (fromIntegral mlen) pa (fromIntegral alen) nullPtr pn pk
where mlen = S.length msg
alen = S.length aad
clen = mlen
tlen = Bytes.aead_xchacha20poly1305_ietf_ABYTES
aeadOpenDetached :: Key -> Nonce
-> ByteString
-> ByteString
-> ByteString
-> Maybe ByteString
aeadOpenDetached (Key key) (Nonce nonce) tag cipher aad
| S.length tag /= tlen = Nothing
| otherwise =
let (err, vec) = buildUnsafeByteString len $ \pm ->
constByteStrings [key, tag, cipher, aad, nonce] $ \
[(pk, _), (pt, _), (pc, _), (pa, _), (pn, _)] ->
c_aead_open_detached pm nullPtr pc (fromIntegral len) pt pa (fromIntegral alen) pn pk
in hush . handleErrno err $ vec
where len = S.length cipher
alen = S.length aad
tlen = Bytes.aead_xchacha20poly1305_ietf_ABYTES
foreign import ccall "crypto_aead_xchacha20poly1305_ietf_encrypt"
c_aead :: Ptr CChar
-> Ptr CULLong
-> Ptr CChar
-> CULLong
-> Ptr CChar
-> CULLong
-> Ptr CChar
-> Ptr CChar
-> Ptr CChar
-> IO CInt
foreign import ccall "crypto_aead_xchacha20poly1305_ietf_decrypt"
c_aead_open :: Ptr CChar
-> Ptr CULLong
-> Ptr CChar
-> Ptr CChar
-> CULLong
-> Ptr CChar
-> CULLong
-> Ptr CChar
-> Ptr CChar
-> IO CInt
foreign import ccall "crypto_aead_xchacha20poly1305_ietf_encrypt_detached"
c_aead_detached :: Ptr CChar
-> Ptr CChar
-> Ptr CULLong
-> Ptr CChar
-> CULLong
-> Ptr CChar
-> CULLong
-> Ptr CChar
-> Ptr CChar
-> Ptr CChar
-> IO CInt
foreign import ccall "crypto_aead_xchacha20poly1305_ietf_decrypt_detached"
c_aead_open_detached :: Ptr CChar
-> Ptr CChar
-> Ptr CChar
-> CULLong
-> Ptr CChar
-> Ptr CChar
-> CULLong
-> Ptr CChar
-> Ptr CChar
-> IO CInt