{-# LANGUAGE ForeignFunctionInterface #-}
{-# LANGUAGE GeneralizedNewtypeDeriving #-}
module Crypto.Cipher.RC4 (
    initialize,
    combine,
    generate,
    State,
) where
import Crypto.Internal.ByteArray (
    ByteArray,
    ByteArrayAccess,
    ScrubbedBytes,
 )
import qualified Crypto.Internal.ByteArray as B
import Data.Word
import Foreign.Ptr
import Crypto.Internal.Compat
import Crypto.Internal.Imports
newtype State = State ScrubbedBytes
    deriving (State -> Int
(State -> Int)
-> (forall p a. State -> (Ptr p -> IO a) -> IO a)
-> (forall p. State -> Ptr p -> IO ())
-> ByteArrayAccess State
forall p. State -> Ptr p -> IO ()
forall ba.
(ba -> Int)
-> (forall p a. ba -> (Ptr p -> IO a) -> IO a)
-> (forall p. ba -> Ptr p -> IO ())
-> ByteArrayAccess ba
forall p a. State -> (Ptr p -> IO a) -> IO a
$clength :: State -> Int
length :: State -> Int
$cwithByteArray :: forall p a. State -> (Ptr p -> IO a) -> IO a
withByteArray :: forall p a. State -> (Ptr p -> IO a) -> IO a
$ccopyByteArrayToPtr :: forall p. State -> Ptr p -> IO ()
copyByteArrayToPtr :: forall p. State -> Ptr p -> IO ()
ByteArrayAccess, State -> ()
(State -> ()) -> NFData State
forall a. (a -> ()) -> NFData a
$crnf :: State -> ()
rnf :: State -> ()
NFData)
foreign import ccall unsafe "crypton_rc4.h crypton_rc4_init"
    c_rc4_init
        :: Ptr Word8
        
        -> Word32
        
        -> Ptr State
        
        -> IO ()
foreign import ccall unsafe "crypton_rc4.h crypton_rc4_combine"
    c_rc4_combine
        :: Ptr State
        
        -> Ptr Word8
        
        -> Word32
        
        -> Ptr Word8
        
        -> IO ()
initialize
    :: ByteArrayAccess key
    => key
    
    -> State
    
initialize :: forall key. ByteArrayAccess key => key -> State
initialize key
key = IO State -> State
forall a. IO a -> a
unsafeDoIO (IO State -> State) -> IO State -> State
forall a b. (a -> b) -> a -> b
$ do
    ScrubbedBytes
st <- Int -> (Ptr Any -> IO ()) -> IO ScrubbedBytes
forall ba p. ByteArray ba => Int -> (Ptr p -> IO ()) -> IO ba
B.alloc Int
264 ((Ptr Any -> IO ()) -> IO ScrubbedBytes)
-> (Ptr Any -> IO ()) -> IO ScrubbedBytes
forall a b. (a -> b) -> a -> b
$ \Ptr Any
stPtr ->
        key -> (Ptr Word8 -> IO ()) -> IO ()
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. key -> (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
$ \Ptr Word8
keyPtr -> Ptr Word8 -> Word32 -> Ptr State -> IO ()
c_rc4_init Ptr Word8
keyPtr (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral (Int -> Word32) -> Int -> Word32
forall a b. (a -> b) -> a -> b
$ key -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length key
key) (Ptr Any -> Ptr State
forall a b. Ptr a -> Ptr b
castPtr Ptr Any
stPtr)
    State -> IO State
forall a. a -> IO a
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
st
generate :: ByteArray ba => State -> Int -> (State, ba)
generate :: forall ba. ByteArray ba => State -> Int -> (State, ba)
generate State
ctx Int
len = State -> ba -> (State, ba)
forall ba. ByteArray ba => State -> ba -> (State, ba)
combine State
ctx (Int -> ba
forall ba. ByteArray ba => Int -> ba
B.zero Int
len)
combine
    :: ByteArray ba
    => State
    
    -> ba
    
    -> (State, ba)
    
combine :: forall ba. ByteArray ba => State -> ba -> (State, ba)
combine (State ScrubbedBytes
prevSt) ba
clearText = IO (State, ba) -> (State, ba)
forall a. IO a -> a
unsafeDoIO (IO (State, ba) -> (State, ba)) -> IO (State, ba) -> (State, ba)
forall a b. (a -> b) -> a -> b
$
    Int -> (Ptr Word8 -> IO State) -> IO (State, ba)
forall ba p a. ByteArray ba => Int -> (Ptr p -> IO a) -> IO (a, ba)
forall p a. Int -> (Ptr p -> IO a) -> IO (a, ba)
B.allocRet Int
len ((Ptr Word8 -> IO State) -> IO (State, ba))
-> (Ptr Word8 -> IO State) -> IO (State, ba)
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
outptr ->
        ba -> (Ptr Word8 -> IO State) -> IO State
forall ba p a. ByteArrayAccess ba => ba -> (Ptr p -> IO a) -> IO a
forall p a. ba -> (Ptr p -> IO a) -> IO a
B.withByteArray ba
clearText ((Ptr Word8 -> IO State) -> IO State)
-> (Ptr Word8 -> IO State) -> IO State
forall a b. (a -> b) -> a -> b
$ \Ptr Word8
clearPtr -> do
            ScrubbedBytes
st <- ScrubbedBytes -> (Ptr Any -> IO ()) -> IO ScrubbedBytes
forall bs1 bs2 p.
(ByteArrayAccess bs1, ByteArray bs2) =>
bs1 -> (Ptr p -> IO ()) -> IO bs2
B.copy ScrubbedBytes
prevSt ((Ptr Any -> IO ()) -> IO ScrubbedBytes)
-> (Ptr Any -> IO ()) -> IO ScrubbedBytes
forall a b. (a -> b) -> a -> b
$ \Ptr Any
stPtr ->
                Ptr State -> Ptr Word8 -> Word32 -> Ptr Word8 -> IO ()
c_rc4_combine (Ptr Any -> Ptr State
forall a b. Ptr a -> Ptr b
castPtr Ptr Any
stPtr) Ptr Word8
clearPtr (Int -> Word32
forall a b. (Integral a, Num b) => a -> b
fromIntegral Int
len) Ptr Word8
outptr
            State -> IO State
forall a. a -> IO a
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
st
  where
    
    len :: Int
len = ba -> Int
forall ba. ByteArrayAccess ba => ba -> Int
B.length ba
clearText