{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Cipher.RC4
( initialize
, combine
, generate
, State
) where
import Data.Word
import Foreign.Ptr
import Crypto.Internal.ByteArray (ScrubbedBytes, ByteArray, ByteArrayAccess)
import qualified Crypto.Internal.ByteArray as B
import Crypto.Internal.Compat
import Crypto.Internal.Imports
newtype State = State ScrubbedBytes
deriving (ByteArrayAccess,NFData)
foreign import ccall unsafe "cryptonite_rc4.h cryptonite_rc4_init"
c_rc4_init :: Ptr Word8
-> Word32
-> Ptr State
-> IO ()
foreign import ccall unsafe "cryptonite_rc4.h cryptonite_rc4_combine"
c_rc4_combine :: Ptr State
-> Ptr Word8
-> Word32
-> Ptr Word8
-> IO ()
initialize :: ByteArrayAccess key
=> key
-> State
initialize key = unsafeDoIO $ do
st <- B.alloc 264 $ \stPtr ->
B.withByteArray key $ \keyPtr -> c_rc4_init keyPtr (fromIntegral $ B.length key) (castPtr stPtr)
return $ State st
generate :: ByteArray ba => State -> Int -> (State, ba)
generate ctx len = combine ctx (B.zero len)
combine :: ByteArray ba
=> State
-> ba
-> (State, ba)
combine (State prevSt) clearText = unsafeDoIO $
B.allocRet len $ \outptr ->
B.withByteArray clearText $ \clearPtr -> do
st <- B.copy prevSt $ \stPtr ->
c_rc4_combine (castPtr stPtr) clearPtr (fromIntegral len) outptr
return $! State st
where len = B.length clearText