This commit is contained in:
Vincent Hanquez 2014-07-21 10:58:42 +01:00
parent 7185a5b871
commit f2bfecfa3e
6 changed files with 207 additions and 0 deletions

92
Crypto/Cipher/RC4.hs Normal file
View File

@ -0,0 +1,92 @@
{-# LANGUAGE ForeignFunctionInterface, CPP #-}
-- |
-- Module : Crypto.Cipher.RC4
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : stable
-- Portability : Good
--
-- Simple implementation of the RC4 stream cipher.
-- http://en.wikipedia.org/wiki/RC4
--
-- Initial FFI implementation by Peter White <peter@janrain.com>
--
-- Reorganized and simplified to have an opaque context.
--
module Crypto.Cipher.RC4
( initialize
, combine
, generate
, State
) where
import Data.Word
import Data.Byteable
import Foreign.Ptr
import Foreign.ForeignPtr
import System.IO.Unsafe
import Data.Byteable
import Data.ByteString (ByteString)
import qualified Data.ByteString as B
import qualified Data.ByteString.Internal as B
import Control.Applicative ((<$>))
----------------------------------------------------------------------
unsafeDoIO :: IO a -> a
#if __GLASGOW_HASKELL__ > 704
unsafeDoIO = unsafeDupablePerformIO
#else
unsafeDoIO = unsafePerformIO
#endif
-- | The encryption state for RC4
newtype State = State ByteString
-- | C Call for initializing the encryptor
foreign import ccall unsafe "cryptonite_rc4.h cryptonite_rc4_init"
c_rc4_init :: Ptr Word8 -- ^ The rc4 key
-> Word32 -- ^ The key length
-> Ptr State -- ^ The context
-> IO ()
foreign import ccall unsafe "cryptonite_rc4.h cryptonite_rc4_combine"
c_rc4_combine :: Ptr State -- ^ Pointer to the permutation
-> Ptr Word8 -- ^ Pointer to the clear text
-> Word32 -- ^ Length of the clear text
-> Ptr Word8 -- ^ Output buffer
-> IO ()
withByteStringPtr :: ByteString -> (Ptr Word8 -> IO a) -> IO a
withByteStringPtr b f = withForeignPtr fptr $ \ptr -> f (ptr `plusPtr` off)
where (fptr, off, _) = B.toForeignPtr b
-- | RC4 context initialization.
--
-- seed the context with an initial key. the key size need to be
-- adequate otherwise security takes a hit.
initialize :: Byteable key
=> key -- ^ The key
-> State -- ^ The RC4 context with the key mixed in
initialize key = unsafeDoIO $ do
State <$> (B.create 264 $ \ctx -> withBytePtr key $ \keyPtr -> c_rc4_init (castPtr keyPtr) (fromIntegral $ byteableLength key) (castPtr ctx))
-- | generate the next len bytes of the rc4 stream without combining
-- it to anything.
generate :: State -> Int -> (State, ByteString)
generate ctx len = combine ctx (B.replicate len 0)
-- | RC4 xor combination of the rc4 stream with an input
combine :: State -- ^ rc4 context
-> ByteString -- ^ input
-> (State, ByteString) -- ^ new rc4 context, and the output
combine (State cctx) clearText = unsafeDoIO $
B.mallocByteString 264 >>= \dctx ->
B.mallocByteString len >>= \outfptr ->
withByteStringPtr clearText $ \clearPtr ->
withByteStringPtr cctx $ \srcState ->
withForeignPtr dctx $ \dstState -> do
withForeignPtr outfptr $ \outptr -> do
B.memcpy dstState srcState 264
c_rc4_combine (castPtr dstState) clearPtr (fromIntegral len) outptr
return $! (State $! B.PS dctx 0 264, B.PS outfptr 0 len)
where len = B.length clearText

63
cbits/cryptonite_rc4.c Normal file
View File

@ -0,0 +1,63 @@
/* initial implementation by
* Peter White <peter@janrain.com>
*/
/* C Standard includes */
#include <stdlib.h>
#include <stdio.h>
#include <string.h>
#include <stdint.h>
/* Local include */
#include "cryptonite_rc4.h"
/* Swap array elements i=State[i] and b=State[j]. */
static void swap(uint8_t *i, uint8_t *j)
{
uint8_t temp;
temp = *i;
*i = *j;
*j = temp;
}
/* Key scheduling algorithm. Swap array elements based on the key. */
void cryptonite_rc4_init(uint8_t *key, uint32_t keylen, struct rc4_ctx *ctx)
{
uint32_t i, j;
memset(ctx, 0, sizeof(struct rc4_ctx));
/* initialize context */
for (i = 0; i < 256; i++)
ctx->state[i] = i;
for (i = j = 0; i < 256; i++) {
j = (j + ctx->state[i] + key[i % keylen]) % 256;
swap(&ctx->state[i], &ctx->state[j]);
}
}
/* Combine the stream generated by the rc4 with some input */
void cryptonite_rc4_combine(struct rc4_ctx *ctx, uint8_t *input, uint32_t len, uint8_t *output)
{
uint32_t i = ctx->i;
uint32_t j = ctx->j;
uint32_t m;
uint8_t si, sj;
/* The RC4 algorithm */
for (m = 0; m < len; m++) {
i = (i + 1) & 0xff;
si = ctx->state[i];
j = (j + si) & 0xff;
sj = ctx->state[j];
/* swap(&state[i], &state[j]); */
ctx->state[i] = sj;
ctx->state[j] = si;
/* Xor the key stream value into the input */
*output++ = *input++ ^ (ctx->state[(si + sj) & 0xff]);
}
/* Output new S-box indices */
ctx->i = i;
ctx->j = j;
}

14
cbits/cryptonite_rc4.h Normal file
View File

@ -0,0 +1,14 @@
#ifndef CRYPTONITE_RC4_H
# define CRYPTONITE_RC4_H
struct rc4_ctx
{
uint8_t state[256];
uint32_t i;
uint32_t j;
};
void cryptonite_rc4_init(uint8_t * key, uint32_t keylen, struct rc4_ctx *ctx);
void cryptonite_rc4_combine(struct rc4_ctx *ctx, uint8_t *input, uint32_t len, uint8_t *output);
#endif

View File

@ -23,6 +23,7 @@ source-repository head
Library
Exposed-modules: Crypto.Cipher.ChaCha
Crypto.Cipher.Salsa
Crypto.Cipher.RC4
Crypto.MAC.Poly1305
Crypto.MAC.HMAC
Crypto.KDF.PBKDF2
@ -57,6 +58,7 @@ Library
default-language: Haskell2010
C-sources: cbits/cryptonite_chacha.c
, cbits/cryptonite_salsa.c
, cbits/cryptonite_rc4.c
, cbits/cryptonite_poly1305.c
, cbits/cryptonite_sha1.c
, cbits/cryptonite_sha256.c

34
tests/KAT_RC4.hs Normal file
View File

@ -0,0 +1,34 @@
{-# LANGUAGE ViewPatterns #-}
{-# LANGUAGE OverloadedStrings #-}
module KAT_RC4 where
import Test.Tasty
import Test.Tasty.HUnit
import Data.ByteString (ByteString)
import Data.ByteString.Char8 ()
import qualified Crypto.Cipher.RC4 as RC4
-- taken from wikipedia pages
vectors :: [(ByteString, ByteString, ByteString)]
vectors =
[ ("Key"
,"Plaintext"
,"\xBB\xF3\x16\xE8\xD9\x40\xAF\x0A\xD3"
)
, ("Wiki"
,"pedia"
,"\x10\x21\xBF\x04\x20"
)
, ("Secret"
,"Attack at dawn"
,"\x45\xA0\x1F\x64\x5F\xC3\x5B\x38\x35\x52\x54\x4B\x9B\xF5"
)
]
tests = testGroup "RC4"
$ map toKatTest $ zip is vectors
where toKatTest (i, (key, plainText, cipherText)) =
testCase (show i) (cipherText @=? snd (RC4.combine (RC4.initialize key) plainText))
is :: [Int]
is = [1..]

View File

@ -18,6 +18,7 @@ import qualified KATSalsa
import qualified KATHash
import qualified KAT_HMAC
import qualified KAT_PBKDF2
import qualified KAT_RC4
b8_128_k0_i0 = "\xe2\x8a\x5f\xa4\xa6\x7f\x8c\x5d\xef\xed\x3e\x6f\xb7\x30\x34\x86\xaa\x84\x27\xd3\x14\x19\xa7\x29\x57\x2d\x77\x79\x53\x49\x11\x20\xb6\x4a\xb8\xe7\x2b\x8d\xeb\x85\xcd\x6a\xea\x7c\xb6\x08\x9a\x10\x18\x24\xbe\xeb\x08\x81\x4a\x42\x8a\xab\x1f\xa2\xc8\x16\x08\x1b\x8a\x26\xaf\x44\x8a\x1b\xa9\x06\x36\x8f\xd8\xc8\x38\x31\xc1\x8c\xec\x8c\xed\x81\x1a\x02\x8e\x67\x5b\x8d\x2b\xe8\xfc\xe0\x81\x16\x5c\xea\xe9\xf1\xd1\xb7\xa9\x75\x49\x77\x49\x48\x05\x69\xce\xb8\x3d\xe6\xa0\xa5\x87\xd4\x98\x4f\x19\x92\x5f\x5d\x33\x8e\x43\x0d"
@ -72,6 +73,7 @@ tests = testGroup "cryptonite"
, KATHash.tests
, KAT_HMAC.tests
, KAT_PBKDF2.tests
, KAT_RC4.tests
]
where chachaRunSimple expected rounds klen nonceLen =
let chacha = ChaCha.initialize rounds (B.replicate klen 0) (B.replicate nonceLen 0)