module Crypto.Cipher.XSalsa
( initialize
, combine
, generate
, State
) where
import Crypto.Internal.ByteArray (ByteArrayAccess, ByteArray, ScrubbedBytes)
import qualified Crypto.Internal.ByteArray as B
import Crypto.Internal.Compat
import Crypto.Internal.Imports
import Foreign.Ptr
import Foreign.Storable
import Foreign.C.Types
import Crypto.Cipher.Salsa hiding (initialize)
initialize :: (ByteArrayAccess key, ByteArrayAccess nonce)
=> Int
-> key
-> nonce
-> State
initialize nbRounds key nonce
| kLen /= 32 = error "XSalsa: key length should be 256 bits"
| nonceLen /= 24 = error "XSalsa: nonce length should be 192 bits"
| not (nbRounds `elem` [8,12,20]) = error "XSalsa: rounds should be 8, 12 or 20"
| otherwise = unsafeDoIO $ do
stPtr <- B.alloc 132 $ \stPtr ->
B.withByteArray nonce $ \noncePtr ->
B.withByteArray key $ \keyPtr ->
ccryptonite_xsalsa_init stPtr (fromIntegral nbRounds) kLen keyPtr nonceLen noncePtr
return $ State stPtr
where kLen = B.length key
nonceLen = B.length nonce
foreign import ccall "cryptonite_xsalsa_init"
ccryptonite_xsalsa_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()