-- |
-- Module      : Crypto.Cipher.XSalsa
-- License     : BSD-style
-- Maintainer  : Brandon Hamilton <brandon.hamilton@gmail.com>
-- Stability   : stable
-- Portability : good
--
-- Implementation of XSalsa20 algorithm
-- <https://cr.yp.to/snuffle/xsalsa-20081128.pdf>
-- Based on the Salsa20 algorithm with 256 bit key extended with 192 bit nonce

{-# LANGUAGE ForeignFunctionInterface #-}
module Crypto.Cipher.XSalsa
    ( initialize
    , combine
    , generate
    , State
    ) where

import           Crypto.Internal.ByteArray (ByteArrayAccess)
import qualified Crypto.Internal.ByteArray as B
import           Crypto.Internal.Compat
import           Crypto.Internal.Imports
import           Foreign.Ptr
import           Crypto.Cipher.Salsa hiding (initialize)

-- | Initialize a new XSalsa context with the number of rounds,
-- the key and the nonce associated.
initialize :: (ByteArrayAccess key, ByteArrayAccess nonce)
           => Int    -- ^ number of rounds (8,12,20)
           -> key    -- ^ the key (256 bits)
           -> nonce  -- ^ the nonce (192 bits)
           -> State  -- ^ the initial XSalsa state
initialize :: Int -> key -> nonce -> State
initialize nbRounds :: Int
nbRounds key :: key
key nonce :: nonce
nonce
    | Int
kLen Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= 32                      = [Char] -> State
forall a. HasCallStack => [Char] -> a
error "XSalsa: key length should be 256 bits"
    | Int
nonceLen Int -> Int -> Bool
forall a. Eq a => a -> a -> Bool
/= 24                  = [Char] -> State
forall a. HasCallStack => [Char] -> a
error "XSalsa: nonce length should be 192 bits"
    | Bool -> Bool
not (Int
nbRounds Int -> [Int] -> Bool
forall (t :: * -> *) a. (Foldable t, Eq a) => a -> t a -> Bool
`elem` [8,12,20]) = [Char] -> State
forall a. HasCallStack => [Char] -> a
error "XSalsa: rounds should be 8, 12 or 20"
    | Bool
otherwise = IO State -> State
forall a. IO a -> a
unsafeDoIO (IO State -> State) -> IO State -> State
forall a b. (a -> b) -> a -> b
$ do
        ScrubbedBytes
stPtr <- Int -> (Ptr State -> IO ()) -> IO ScrubbedBytes
forall ba p. ByteArray ba => Int -> (Ptr p -> IO ()) -> IO ba
B.alloc 132 ((Ptr State -> IO ()) -> IO ScrubbedBytes)
-> (Ptr State -> IO ()) -> IO ScrubbedBytes
forall a b. (a -> b) -> a -> b
$ \stPtr :: Ptr State
stPtr ->
            nonce -> (Ptr Word8 -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
B.withByteArray nonce
nonce ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \noncePtr :: Ptr Word8
noncePtr  ->
            key -> (Ptr Word8 -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
B.withByteArray key
key   ((Ptr Word8 -> IO ()) -> IO ()) -> (Ptr Word8 -> IO ()) -> IO ()
forall a b. (a -> b) -> a -> b
$ \keyPtr :: Ptr Word8
keyPtr ->
                Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()
ccryptonite_xsalsa_init Ptr State
stPtr Int
nbRounds Int
kLen Ptr Word8
keyPtr Int
nonceLen Ptr Word8
noncePtr
        State -> IO State
forall (m :: * -> *) a. Monad m => a -> m a
return (State -> IO State) -> State -> IO State
forall a b. (a -> b) -> a -> b
$ ScrubbedBytes -> State
State ScrubbedBytes
stPtr
  where kLen :: Int
kLen     = key -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length key
key
        nonceLen :: Int
nonceLen = nonce -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length nonce
nonce

foreign import ccall "cryptonite_xsalsa_init"
    ccryptonite_xsalsa_init :: Ptr State -> Int -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()