initial commit.

This commit is contained in:
Vincent Hanquez 2014-07-04 14:58:01 +01:00
commit fb85f8639f
10 changed files with 755 additions and 0 deletions

5
.gitignore vendored Normal file
View File

@ -0,0 +1,5 @@
*.o
*.hi
*.tix
*.mix
dist

127
Crypto/Cipher/ChaCha.hs Normal file
View File

@ -0,0 +1,127 @@
-- |
-- Module : Crypto.Cipher.ChaCha
-- License : BSD-style
-- Maintainer : Vincent Hanquez <vincent@snarc.org>
-- Stability : stable
-- Portability : good
--
{-# LANGUAGE ForeignFunctionInterface #-}
module Crypto.Cipher.ChaCha
( initialize
, combine
, generate
, State
) where
import Control.Applicative
import Data.SecureMem
import Data.ByteString (ByteString)
import qualified Data.ByteString.Internal as B
import qualified Data.ByteString as B
import Data.Byteable
import Data.Word
import Data.Bits (xor)
import Foreign.Ptr
import Foreign.ForeignPtr
import Foreign.C.Types
import Foreign.Storable
import System.IO.Unsafe
-- | ChaCha context
data State = State Int -- number of rounds
SecureMem -- ChaCha's state
ByteString -- previous generated chunk
round64 :: Int -> (Bool, Int)
round64 len
| len == 0 = (True, 0)
| m == 0 = (True, len)
| otherwise = (False, len + (64 - m))
where m = len `mod` 64
-- | Initialize a new ChaCha context with the number of rounds,
-- the key and the nonce associated.
initialize :: Byteable key
=> Int -- ^ number of rounds (8,12,20)
-> key -- ^ the key (128 or 256 bits)
-> ByteString -- ^ the nonce (64 or 96 bits)
-> State -- ^ the initial ChaCha state
initialize nbRounds key nonce
| not (kLen `elem` [16,32]) = error "ChaCha: key length should be 128 or 256 bits"
| not (nonceLen `elem` [8,12]) = error "ChaCha: nonce length should be 64 or 96 bits"
| not (nbRounds `elem` [8,12,20]) = error "ChaCha: rounds should be 8, 12 or 20"
| otherwise = unsafePerformIO $ do
stPtr <- createSecureMem 64 $ \stPtr ->
withBytePtr nonce $ \noncePtr ->
withBytePtr key $ \keyPtr ->
ccryptonite_chacha_init (castPtr stPtr) kLen keyPtr nonceLen noncePtr
return $ State nbRounds stPtr B.empty
where kLen = byteableLength key
nonceLen = B.length nonce
-- | Combine the chacha output and an arbitrary message with a xor,
-- and return the combined output and the new state.
combine :: State -- ^ the current ChaCha state
-> ByteString -- ^ the source to xor with the generator
-> (ByteString, State)
combine prev@(State nbRounds prevSt prevOut) src
| outputLen == 0 = (B.empty, prev)
| outputLen <= prevBufLen =
-- we have enough byte in the previous buffer to complete the query
-- without having to generate any extra bytes
let (b1,b2) = B.splitAt outputLen prevOut
in (B.pack $ B.zipWith xor b1 src, State nbRounds prevSt b2)
| otherwise = unsafePerformIO $ do
-- adjusted len is the number of bytes lefts to generate after
-- copying from the previous buffer.
let adjustedLen = outputLen - prevBufLen
(roundedAlready, newBytesToGenerate) = round64 adjustedLen
nextBufLen = newBytesToGenerate - adjustedLen
fptr <- B.mallocByteString (newBytesToGenerate + prevBufLen)
newSt <- withForeignPtr fptr $ \dstPtr ->
withBytePtr src $ \srcPtr -> do
-- copy the previous buffer by xor if any
withBytePtr prevOut $ \prevPtr ->
loopXor dstPtr srcPtr prevPtr prevBufLen
-- then create a new mutable copy of state
st <- secureMemCopy prevSt
withSecureMemPtr st $ \stPtr ->
ccryptonite_chacha_combine nbRounds
(dstPtr `plusPtr` prevBufLen)
(castPtr stPtr)
(srcPtr `plusPtr` prevBufLen)
(fromIntegral newBytesToGenerate)
return st
-- return combined byte
return ( B.PS fptr 0 outputLen
, State nbRounds newSt (if roundedAlready then B.empty else B.PS fptr outputLen nextBufLen))
where
outputLen = B.length src
prevBufLen = B.length prevOut
loopXor :: Ptr Word8 -> Ptr Word8 -> Ptr Word8 -> Int -> IO ()
loopXor _ _ _ 0 = return ()
loopXor d s1 s2 n = do
(xor <$> peek s1 <*> peek s2) >>= poke d
loopXor (d `plusPtr` 1) (s1 `plusPtr` 1) (s2 `plusPtr` 1) (n-1)
-- | Generate a number of bytes from the ChaCha output directly
--
-- TODO: use chacha_generate directly instead of using combine xor'ing with 0.
generate :: State -- ^ the current ChaCha state
-> Int -- ^ the length of data to generate
-> (ByteString, State)
generate st len = combine st (B.replicate len 0)
foreign import ccall "cryptonite_chacha_init"
ccryptonite_chacha_init :: Ptr State -> Int -> Ptr Word8 -> Int -> Ptr Word8 -> IO ()
foreign import ccall "cryptonite_chacha_combine"
ccryptonite_chacha_combine :: Int -> Ptr Word8 -> Ptr State -> Ptr Word8 -> CUInt -> IO ()
{-
foreign import ccall "cryptonite_chacha_generate"
ccryptonite_chacha_generate :: Int -> Ptr Word8 -> Ptr State -> CUInt -> IO ()
-}

27
LICENSE Normal file
View File

@ -0,0 +1,27 @@
Copyright (c) 2014 Vincent Hanquez <vincent@snarc.org>
All rights reserved.
Redistribution and use in source and binary forms, with or without
modification, are permitted provided that the following conditions
are met:
1. Redistributions of source code must retain the above copyright
notice, this list of conditions and the following disclaimer.
2. Redistributions in binary form must reproduce the above copyright
notice, this list of conditions and the following disclaimer in the
documentation and/or other materials provided with the distribution.
3. Neither the name of the author nor the names of his contributors
may be used to endorse or promote products derived from this software
without specific prior written permission.
THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS AS IS'' AND
ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE
FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
SUCH DAMAGE.

24
README.md Normal file
View File

@ -0,0 +1,24 @@
cryptonite
==========
Cryptonite is a haskell repository of cryptographic primitives. Each crypto
algorithm have specificities, that are hard to wrap in common APIs and types,
so instead of trying to provide a common ground for algorithms that wouldn't
allow to provide all different usage or a really complicated system, this just
provide a non-consistant low-level API.
If you have no idea what're you doing, please do not use this directly, rely on
higher level protocols or higher level implementation.
Documentation: [cryptonite on hackage](http://hackage.haskell.org/package/cryptonite)
Links
-----
* [ChaCha](http://cr.yp.to/chacha.html)
* [ChaCha-test-vectors](https://github.com/secworks/chacha_testvectors.git)
TODO
----
* remove copy of read-only part of ChaCha state by splitting the stuff in two.

2
Setup.hs Normal file
View File

@ -0,0 +1,2 @@
import Distribution.Simple
main = defaultMain

238
cbits/cryptonite_bitfn.h Normal file
View File

@ -0,0 +1,238 @@
/*
* Copyright (C) 2006-2014 Vincent Hanquez <vincent@snarc.org>
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
*
* THIS SOFTWARE IS PROVIDED BY THE AUTHOR ``AS IS'' AND ANY EXPRESS OR
* IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE IMPLIED WARRANTIES
* OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE ARE DISCLAIMED.
* IN NO EVENT SHALL THE AUTHOR BE LIABLE FOR ANY DIRECT, INDIRECT,
* INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL DAMAGES (INCLUDING, BUT
* NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS OR SERVICES; LOSS OF USE,
* DATA, OR PROFITS; OR BUSINESS INTERRUPTION) HOWEVER CAUSED AND ON ANY
* THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT LIABILITY, OR TORT
* (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY OUT OF THE USE OF
* THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF SUCH DAMAGE.
*/
#ifndef BITFN_H
#define BITFN_H
#include <stdint.h>
#ifndef NO_INLINE_ASM
/**********************************************************/
# if (defined(__i386__))
# define ARCH_HAS_SWAP32
static inline uint32_t bitfn_swap32(uint32_t a)
{
asm ("bswap %0" : "=r" (a) : "0" (a));
return a;
}
/**********************************************************/
# elif (defined(__arm__))
# define ARCH_HAS_SWAP32
static inline uint32_t bitfn_swap32(uint32_t a)
{
uint32_t tmp = a;
asm volatile ("eor %1, %0, %0, ror #16\n"
"bic %1, %1, #0xff0000\n"
"mov %0, %0, ror #8\n"
"eor %0, %0, %1, lsr #8\n"
: "=r" (a), "=r" (tmp) : "0" (a), "1" (tmp));
return a;
}
/**********************************************************/
# elif defined(__x86_64__)
# define ARCH_HAS_SWAP32
# define ARCH_HAS_SWAP64
static inline uint32_t bitfn_swap32(uint32_t a)
{
asm ("bswap %0" : "=r" (a) : "0" (a));
return a;
}
static inline uint64_t bitfn_swap64(uint64_t a)
{
asm ("bswap %0" : "=r" (a) : "0" (a));
return a;
}
# endif
#endif /* NO_INLINE_ASM */
/**********************************************************/
#ifndef ARCH_HAS_ROL32
static inline uint32_t rol32(uint32_t word, uint32_t shift)
{
return (word << shift) | (word >> (32 - shift));
}
#endif
#ifndef ARCH_HAS_ROR32
static inline uint32_t ror32(uint32_t word, uint32_t shift)
{
return (word >> shift) | (word << (32 - shift));
}
#endif
#ifndef ARCH_HAS_ROL64
static inline uint64_t rol64(uint64_t word, uint32_t shift)
{
return (word << shift) | (word >> (64 - shift));
}
#endif
#ifndef ARCH_HAS_ROR64
static inline uint64_t ror64(uint64_t word, uint32_t shift)
{
return (word >> shift) | (word << (64 - shift));
}
#endif
#ifndef ARCH_HAS_SWAP32
static inline uint32_t bitfn_swap32(uint32_t a)
{
return (a << 24) | ((a & 0xff00) << 8) | ((a >> 8) & 0xff00) | (a >> 24);
}
#endif
#ifndef ARCH_HAS_ARRAY_SWAP32
static inline void array_swap32(uint32_t *d, uint32_t *s, uint32_t nb)
{
while (nb--)
*d++ = bitfn_swap32(*s++);
}
#endif
#ifndef ARCH_HAS_SWAP64
static inline uint64_t bitfn_swap64(uint64_t a)
{
return ((uint64_t) bitfn_swap32((uint32_t) (a >> 32))) |
(((uint64_t) bitfn_swap32((uint32_t) a)) << 32);
}
#endif
#ifndef ARCH_HAS_ARRAY_SWAP64
static inline void array_swap64(uint64_t *d, uint64_t *s, uint32_t nb)
{
while (nb--)
*d++ = bitfn_swap64(*s++);
}
#endif
#ifndef ARCH_HAS_MEMORY_ZERO
static inline void memory_zero(void *ptr, uint32_t len)
{
uint32_t *ptr32 = ptr;
uint8_t *ptr8;
int i;
for (i = 0; i < len / 4; i++)
*ptr32++ = 0;
if (len % 4) {
ptr8 = (uint8_t *) ptr32;
for (i = len % 4; i >= 0; i--)
ptr8[i] = 0;
}
}
#endif
#ifndef ARCH_HAS_ARRAY_COPY32
static inline void array_copy32(uint32_t *d, uint32_t *s, uint32_t nb)
{
while (nb--) *d++ = *s++;
}
#endif
#ifndef ARCH_HAS_ARRAY_COPY64
static inline void array_copy64(uint64_t *d, uint64_t *s, uint32_t nb)
{
while (nb--) *d++ = *s++;
}
#endif
#ifdef __MINGW32__
# define LITTLE_ENDIAN 1234
# define BYTE_ORDER LITTLE_ENDIAN
#elif defined(__FreeBSD__) || defined(__DragonFly__) || defined(__NetBSD__)
# include <sys/endian.h>
#elif defined(__OpenBSD__) || defined(__SVR4)
# include <sys/types.h>
#elif defined(__APPLE__)
# include <machine/endian.h>
#elif defined( BSD ) && ( BSD >= 199103 )
# include <machine/endian.h>
#elif defined( __QNXNTO__ ) && defined( __LITTLEENDIAN__ )
# define LITTLE_ENDIAN 1234
# define BYTE_ORDER LITTLE_ENDIAN
#elif defined( __QNXNTO__ ) && defined( __BIGENDIAN__ )
# define BIG_ENDIAN 1234
# define BYTE_ORDER BIG_ENDIAN
#else
# include <endian.h>
#endif
/* big endian to cpu */
#if LITTLE_ENDIAN == BYTE_ORDER
# define be32_to_cpu(a) bitfn_swap32(a)
# define cpu_to_be32(a) bitfn_swap32(a)
# define le32_to_cpu(a) (a)
# define cpu_to_le32(a) (a)
# define be64_to_cpu(a) bitfn_swap64(a)
# define cpu_to_be64(a) bitfn_swap64(a)
# define le64_to_cpu(a) (a)
# define cpu_to_le64(a) (a)
# define cpu_to_le32_array(d, s, l) array_copy32(d, s, l)
# define le32_to_cpu_array(d, s, l) array_copy32(d, s, l)
# define cpu_to_be32_array(d, s, l) array_swap32(d, s, l)
# define be32_to_cpu_array(d, s, l) array_swap32(d, s, l)
# define cpu_to_le64_array(d, s, l) array_copy64(d, s, l)
# define le64_to_cpu_array(d, s, l) array_copy64(d, s, l)
# define cpu_to_be64_array(d, s, l) array_swap64(d, s, l)
# define be64_to_cpu_array(d, s, l) array_swap64(d, s, l)
# define ror32_be(a, s) rol32(a, s)
# define rol32_be(a, s) ror32(a, s)
# define ARCH_IS_LITTLE_ENDIAN
#elif BIG_ENDIAN == BYTE_ORDER
# define be32_to_cpu(a) (a)
# define cpu_to_be32(a) (a)
# define be64_to_cpu(a) (a)
# define cpu_to_be64(a) (a)
# define le64_to_cpu(a) bitfn_swap64(a)
# define cpu_to_le64(a) bitfn_swap64(a)
# define le32_to_cpu(a) bitfn_swap32(a)
# define cpu_to_le32(a) bitfn_swap32(a)
# define cpu_to_le32_array(d, s, l) array_swap32(d, s, l)
# define le32_to_cpu_array(d, s, l) array_swap32(d, s, l)
# define cpu_to_be32_array(d, s, l) array_copy32(d, s, l)
# define be32_to_cpu_array(d, s, l) array_copy32(d, s, l)
# define cpu_to_le64_array(d, s, l) array_swap64(d, s, l)
# define le64_to_cpu_array(d, s, l) array_swap64(d, s, l)
# define cpu_to_be64_array(d, s, l) array_copy64(d, s, l)
# define be64_to_cpu_array(d, s, l) array_copy64(d, s, l)
# define ror32_be(a, s) ror32(a, s)
# define rol32_be(a, s) rol32(a, s)
# define ARCH_IS_BIG_ENDIAN
#else
# error "endian not supported"
#endif
#endif /* !BITFN_H */

199
cbits/cryptonite_chacha.c Normal file
View File

@ -0,0 +1,199 @@
/*
* Copyright (c) 2014 Vincent Hanquez <vincent@snarc.org>
*
* All rights reserved.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. Neither the name of the author nor the names of his contributors
* may be used to endorse or promote products derived from this software
* without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
* ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE
* FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
* DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
* OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
* LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
* OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
* SUCH DAMAGE.
*/
#include <stdint.h>
#include "cryptonite_chacha.h"
#include "cryptonite_bitfn.h"
#include <stdio.h>
#define USE_8BITS 0
#define QR(a,b,c,d) \
a += b; d = rol32(d ^ a,16); \
c += d; b = rol32(b ^ c,12); \
a += b; d = rol32(d ^ a, 8); \
c += d; b = rol32(b ^ c, 7);
static const char sigma[16] = "expand 32-byte k";
static const char tau[16] = "expand 16-byte k";
uint32_t load32(const uint8_t *p)
{
return le32_to_cpu(*((uint32_t *) p));
}
static void chacha_core(int rounds, block *out, const cryptonite_chacha_state *in)
{
uint32_t x0, x1, x2, x3, x4, x5, x6, x7, x8, x9, x10, x11, x12, x13, x14, x15;
int i;
x0 = in->d[0]; x1 = in->d[1]; x2 = in->d[2]; x3 = in->d[3];
x4 = in->d[4]; x5 = in->d[5]; x6 = in->d[6]; x7 = in->d[7];
x8 = in->d[8]; x9 = in->d[9]; x10 = in->d[10]; x11 = in->d[11];
x12 = in->d[12]; x13 = in->d[13]; x14 = in->d[14]; x15 = in->d[15];
for (i = rounds; i > 0; i -= 2) {
QR(x0, x4, x8, x12);
QR(x1, x5, x9, x13);
QR(x2, x6, x10, x14);
QR(x3, x7, x11, x15);
QR(x0, x5, x10, x15);
QR(x1, x6, x11, x12);
QR(x2, x7, x8, x13);
QR(x3, x4, x9, x14);
}
x0 += in->d[0]; x1 += in->d[1]; x2 += in->d[2]; x3 += in->d[3];
x4 += in->d[4]; x5 += in->d[5]; x6 += in->d[6]; x7 += in->d[7];
x8 += in->d[8]; x9 += in->d[9]; x10 += in->d[10]; x11 += in->d[11];
x12 += in->d[12]; x13 += in->d[13]; x14 += in->d[14]; x15 += in->d[15];
out->d[0] = cpu_to_le32(x0);
out->d[1] = cpu_to_le32(x1);
out->d[2] = cpu_to_le32(x2);
out->d[3] = cpu_to_le32(x3);
out->d[4] = cpu_to_le32(x4);
out->d[5] = cpu_to_le32(x5);
out->d[6] = cpu_to_le32(x6);
out->d[7] = cpu_to_le32(x7);
out->d[8] = cpu_to_le32(x8);
out->d[9] = cpu_to_le32(x9);
out->d[10] = cpu_to_le32(x10);
out->d[11] = cpu_to_le32(x11);
out->d[12] = cpu_to_le32(x12);
out->d[13] = cpu_to_le32(x13);
out->d[14] = cpu_to_le32(x14);
out->d[15] = cpu_to_le32(x15);
}
/* only 2 valids values are 256 (32) and 128 (16) */
void cryptonite_chacha_init(cryptonite_chacha_state *st,
uint32_t keylen, const uint8_t *key,
uint32_t ivlen, const uint8_t *iv)
{
const char *constants = (keylen == 32) ? sigma : tau;
int i;
st->d[0] = load32(constants + 0);
st->d[1] = load32(constants + 4);
st->d[2] = load32(constants + 8);
st->d[3] = load32(constants + 12);
st->d[4] = load32(key + 0);
st->d[5] = load32(key + 4);
st->d[6] = load32(key + 8);
st->d[7] = load32(key + 12);
/* we repeat the key on 128 bits */
if (keylen == 32)
key += 16;
st->d[8] = load32(key + 0);
st->d[9] = load32(key + 4);
st->d[10] = load32(key + 8);
st->d[11] = load32(key + 12);
st->d[12] = 0;
switch (ivlen) {
case 8:
st->d[13] = 0;
st->d[14] = load32(iv + 0);
st->d[15] = load32(iv + 4);
break;
case 12:
st->d[13] = load32(iv + 0);
st->d[14] = load32(iv + 4);
st->d[15] = load32(iv + 8);
default:
return;
}
}
void cryptonite_chacha_combine(uint32_t rounds, block *dst, cryptonite_chacha_state *st, const block *src, uint32_t bytes)
{
block out;
int i;
if (!bytes)
return;
for (;; bytes -= 64, src += 1, dst += 1) {
chacha_core(rounds, &out, st);
st->d[12] += 1;
if (st->d[12] == 0)
st->d[13] += 1;
if (bytes <= 64) {
for (i = 0; i < bytes; i++)
dst->b[i] = src->b[i] ^ out.b[i];
for (; i < 64; i++)
dst->b[i] = out.b[i];
return;
}
#if USE_8BITS
for (i = 0; i < 64; ++i)
dst->b[i] = src->b[i] ^ out.b[i];
#else
/* fast copy using 64 bits */
for (i = 0; i < 8; i++)
dst->q[i] = src->q[i] ^ out.q[i];
#endif
}
}
void cryptonite_chacha_generate(uint32_t rounds, block *dst, cryptonite_chacha_state *st, uint32_t bytes)
{
block out;
int i;
if (!bytes)
return;
for (;; bytes -= 64, dst += 64) {
chacha_core(rounds, &out, st);
st->d[12] += 1;
if (st->d[12] == 0)
st->d[13] += 1;
if (bytes <= 64) {
for (i = 0; i < bytes; ++i)
dst->b[i] = out.b[i];
return;
}
#if USE_8BITS
for (i = 0; i < 64; ++i)
dst->b[i] = out.b[i];
#else
for (i = 0; i < 8; i++)
dst->q[i] = out.q[i];
#endif
}
}

45
cbits/cryptonite_chacha.h Normal file
View File

@ -0,0 +1,45 @@
/*
* Copyright (c) 2014 Vincent Hanquez <vincent@snarc.org>
*
* All rights reserved.
*
* Redistribution and use in source and binary forms, with or without
* modification, are permitted provided that the following conditions
* are met:
* 1. Redistributions of source code must retain the above copyright
* notice, this list of conditions and the following disclaimer.
* 2. Redistributions in binary form must reproduce the above copyright
* notice, this list of conditions and the following disclaimer in the
* documentation and/or other materials provided with the distribution.
* 3. Neither the name of the author nor the names of his contributors
* may be used to endorse or promote products derived from this software
* without specific prior written permission.
*
* THIS SOFTWARE IS PROVIDED BY THE REGENTS AND CONTRIBUTORS ``AS IS'' AND
* ANY EXPRESS OR IMPLIED WARRANTIES, INCLUDING, BUT NOT LIMITED TO, THE
* IMPLIED WARRANTIES OF MERCHANTABILITY AND FITNESS FOR A PARTICULAR PURPOSE
* ARE DISCLAIMED. IN NO EVENT SHALL THE AUTHORS OR CONTRIBUTORS BE LIABLE
* FOR ANY DIRECT, INDIRECT, INCIDENTAL, SPECIAL, EXEMPLARY, OR CONSEQUENTIAL
* DAMAGES (INCLUDING, BUT NOT LIMITED TO, PROCUREMENT OF SUBSTITUTE GOODS
* OR SERVICES; LOSS OF USE, DATA, OR PROFITS; OR BUSINESS INTERRUPTION)
* HOWEVER CAUSED AND ON ANY THEORY OF LIABILITY, WHETHER IN CONTRACT, STRICT
* LIABILITY, OR TORT (INCLUDING NEGLIGENCE OR OTHERWISE) ARISING IN ANY WAY
* OUT OF THE USE OF THIS SOFTWARE, EVEN IF ADVISED OF THE POSSIBILITY OF
* SUCH DAMAGE.
*/
#ifndef CRYPTONITE_CHACHA
#define CRYPTONITE_CHACHA
typedef union {
uint64_t q[8];
uint32_t d[16];
uint8_t b[64];
} block;
typedef block cryptonite_chacha_state;
void cryptonite_chacha_init(cryptonite_chacha_state *st, uint32_t keylen, const uint8_t *key, uint32_t ivlen, const uint8_t *iv);
void cryptonite_chacha_combine(uint32_t rounds, block *dst, cryptonite_chacha_state *st, const block *src, uint32_t bytes);
void cryptonite_chacha_generate(uint32_t rounds, block *dst, cryptonite_chacha_state *st, uint32_t bytes);
#endif

46
cryptonite.cabal Normal file
View File

@ -0,0 +1,46 @@
Name: cryptonite
Version: 0.1.0
Synopsis: Crypto stuff
Description: cryptography
License: BSD3
License-file: LICENSE
Copyright: Vincent Hanquez <vincent@snarc.org>
Author: Vincent Hanquez <vincent@snarc.org>
Maintainer: vincent@snarc.org
Category: Cryptography
Stability: experimental
Build-Type: Simple
Homepage: https://github.com/vincenthz/cryptonite
Cabal-Version: >=1.10
extra-source-files: README.md
cbits/*.h
source-repository head
type: git
location: https://github.com/vincenthz/hs-cryptonite
Library
Exposed-modules: Crypto.Cipher.ChaCha
Build-depends: base >= 4 && < 5
, bytestring
, securemem
, byteable
ghc-options: -Wall -fwarn-tabs -optc-O3
default-language: Haskell2010
C-sources: cbits/cryptonite_chacha.c
if (arch(i386) || arch(x86_64))
CPP-options: -DARCH_IS_LITTLE_ENDIAN
Test-Suite test-cryptonite
type: exitcode-stdio-1.0
hs-source-dirs: tests
Main-is: Tests.hs
Build-Depends: base >= 3 && < 5
, bytestring
, mtl
, tasty
, tasty-quickcheck
, tasty-hunit
, cryptonite
ghc-options: -Wall -fno-warn-orphans -fno-warn-missing-signatures
default-language: Haskell2010

42
tests/Tests.hs Normal file
View File

@ -0,0 +1,42 @@
{-# LANGUAGE OverloadedStrings #-}
module Main where
import qualified Data.ByteString as B
import Test.Tasty
import Test.Tasty.QuickCheck
import Test.Tasty.HUnit
import qualified Crypto.Cipher.ChaCha as ChaCha
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"
b12_128_k0_i0 =
"\xe1\x04\x7b\xa9\x47\x6b\xf8\xff\x31\x2c\x01\xb4\x34\x5a\x7d\x8c\xa5\x79\x2b\x0a\xd4\x67\x31\x3f\x1d\xc4\x12\xb5\xfd\xce\x32\x41\x0d\xea\x8b\x68\xbd\x77\x4c\x36\xa9\x20\xf0\x92\xa0\x4d\x3f\x95\x27\x4f\xbe\xff\x97\xbc\x84\x91\xfc\xef\x37\xf8\x59\x70\xb4\x50\x1d\x43\xb6\x1a\x8f\x7e\x19\xfc\xed\xde\xf3\x68\xae\x6b\xfb\x11\x10\x1b\xd9\xfd\x3e\x4d\x12\x7d\xe3\x0d\xb2\xdb\x1b\x47\x2e\x76\x42\x68\x03\xa4\x5e\x15\xb9\x62\x75\x19\x86\xef\x1d\x9d\x50\xf5\x98\xa5\xdc\xdc\x9f\xa5\x29\xa2\x83\x57\x99\x1e\x78\x4e\xa2\x0f"
b20_128_k0_i0 =
"\x89\x67\x09\x52\x60\x83\x64\xfd\x00\xb2\xf9\x09\x36\xf0\x31\xc8\xe7\x56\xe1\x5d\xba\x04\xb8\x49\x3d\x00\x42\x92\x59\xb2\x0f\x46\xcc\x04\xf1\x11\x24\x6b\x6c\x2c\xe0\x66\xbe\x3b\xfb\x32\xd9\xaa\x0f\xdd\xfb\xc1\x21\x23\xd4\xb9\xe4\x4f\x34\xdc\xa0\x5a\x10\x3f\x6c\xd1\x35\xc2\x87\x8c\x83\x2b\x58\x96\xb1\x34\xf6\x14\x2a\x9d\x4d\x8d\x0d\x8f\x10\x26\xd2\x0a\x0a\x81\x51\x2c\xbc\xe6\xe9\x75\x8a\x71\x43\xd0\x21\x97\x80\x22\xa3\x84\x14\x1a\x80\xce\xa3\x06\x2f\x41\xf6\x7a\x75\x2e\x66\xad\x34\x11\x98\x4c\x78\x7e\x30\xad"
b8_256_k0_i0 =
"\x3e\x00\xef\x2f\x89\x5f\x40\xd6\x7f\x5b\xb8\xe8\x1f\x09\xa5\xa1\x2c\x84\x0e\xc3\xce\x9a\x7f\x3b\x18\x1b\xe1\x88\xef\x71\x1a\x1e\x98\x4c\xe1\x72\xb9\x21\x6f\x41\x9f\x44\x53\x67\x45\x6d\x56\x19\x31\x4a\x42\xa3\xda\x86\xb0\x01\x38\x7b\xfd\xb8\x0e\x0c\xfe\x42\xd2\xae\xfa\x0d\xea\xa5\xc1\x51\xbf\x0a\xdb\x6c\x01\xf2\xa5\xad\xc0\xfd\x58\x12\x59\xf9\xa2\xaa\xdc\xf2\x0f\x8f\xd5\x66\xa2\x6b\x50\x32\xec\x38\xbb\xc5\xda\x98\xee\x0c\x6f\x56\x8b\x87\x2a\x65\xa0\x8a\xbf\x25\x1d\xeb\x21\xbb\x4b\x56\xe5\xd8\x82\x1e\x68\xaa"
b12_256_k0_i0 =
"\x9b\xf4\x9a\x6a\x07\x55\xf9\x53\x81\x1f\xce\x12\x5f\x26\x83\xd5\x04\x29\xc3\xbb\x49\xe0\x74\x14\x7e\x00\x89\xa5\x2e\xae\x15\x5f\x05\x64\xf8\x79\xd2\x7a\xe3\xc0\x2c\xe8\x28\x34\xac\xfa\x8c\x79\x3a\x62\x9f\x2c\xa0\xde\x69\x19\x61\x0b\xe8\x2f\x41\x13\x26\xbe\x0b\xd5\x88\x41\x20\x3e\x74\xfe\x86\xfc\x71\x33\x8c\xe0\x17\x3d\xc6\x28\xeb\xb7\x19\xbd\xcb\xcc\x15\x15\x85\x21\x4c\xc0\x89\xb4\x42\x25\x8d\xcd\xa1\x4c\xf1\x11\xc6\x02\xb8\x97\x1b\x8c\xc8\x43\xe9\x1e\x46\xca\x90\x51\x51\xc0\x27\x44\xa6\xb0\x17\xe6\x93\x16"
b20_256_k0_i0 =
"\x76\xb8\xe0\xad\xa0\xf1\x3d\x90\x40\x5d\x6a\xe5\x53\x86\xbd\x28\xbd\xd2\x19\xb8\xa0\x8d\xed\x1a\xa8\x36\xef\xcc\x8b\x77\x0d\xc7\xda\x41\x59\x7c\x51\x57\x48\x8d\x77\x24\xe0\x3f\xb8\xd8\x4a\x37\x6a\x43\xb8\xf4\x15\x18\xa1\x1c\xc3\x87\xb6\x69\xb2\xee\x65\x86\x9f\x07\xe7\xbe\x55\x51\x38\x7a\x98\xba\x97\x7c\x73\x2d\x08\x0d\xcb\x0f\x29\xa0\x48\xe3\x65\x69\x12\xc6\x53\x3e\x32\xee\x7a\xed\x29\xb7\x21\x76\x9c\xe6\x4e\x43\xd5\x71\x33\xb0\x74\xd8\x39\xd5\x31\xed\x1f\x28\x51\x0a\xfb\x45\xac\xe1\x0a\x1f\x4b\x79\x4d\x6f"
tests = testGroup "cryptonite"
[ testGroup "ChaCha"
[ testCase "8-128-K0-I0" (chachaRunSimple b8_128_k0_i0 8 16 8)
, testCase "12-128-K0-I0" (chachaRunSimple b12_128_k0_i0 12 16 8)
, testCase "20-128-K0-I0" (chachaRunSimple b20_128_k0_i0 20 16 8)
, testCase "8-256-K0-I0" (chachaRunSimple b8_256_k0_i0 8 32 8)
, testCase "12-256-K0-I0" (chachaRunSimple b12_256_k0_i0 12 32 8)
, testCase "20-256-K0-I0" (chachaRunSimple b20_256_k0_i0 20 32 8)
]
]
where chachaRunSimple expected rounds klen nonceLen =
let chacha = ChaCha.initialize rounds (B.replicate klen 0) (B.replicate nonceLen 0)
in expected @=? fst (ChaCha.generate chacha (B.length expected))
main = defaultMain tests