Skip to content

Commit

Permalink
Hid nonessential modules. Changed namespace. Various cleanup. Changed…
Browse files Browse the repository at this point in the history
… the way benchmarks are run.
  • Loading branch information
rrnewton committed Aug 25, 2011
1 parent 14bdb2e commit 3ad20dd
Show file tree
Hide file tree
Showing 8 changed files with 175 additions and 181 deletions.
14 changes: 7 additions & 7 deletions Codec/Crypto/ConvertRNG.hs
Expand Up @@ -26,7 +26,7 @@
module Codec.Crypto.ConvertRNG
( BCtoCRG(..), convertCRG
, CRGtoRG()
, CRGtoRG0(..) -- Inefficient version for testing...
, CRGtoRG_Unbuffered(..) -- Inefficient version for testing...
)
where

Expand Down Expand Up @@ -73,21 +73,21 @@ import Foreign.Storable

-- | Converting CryptoRandomGen to RandomGen.
-- This naive version is probably pretty inefficent:
data CRGtoRG0 a = CRGtoRG0 a
instance CryptoRandomGen g => RandomGen (CRGtoRG0 g) where
next (CRGtoRG0 g) =
data CRGtoRG_Unbuffered a = CRGtoRG_Unbuffered a
instance CryptoRandomGen g => RandomGen (CRGtoRG_Unbuffered g) where
next (CRGtoRG_Unbuffered g) =
-- case genBytes (max bytes_in_int (keyLength g `quot` 8)) g of
case genBytes bytes_in_int g of
Left err -> error$ "CryptoRandomGen genBytes error: " ++ show err
Right (bytes,g') ->
case decode bytes of
Left err -> error$ "Deserialization error:"++ show err
Right n -> (n, CRGtoRG0 g')
Right n -> (n, CRGtoRG_Unbuffered g')

split (CRGtoRG0 g) =
split (CRGtoRG_Unbuffered g) =
case splitGen g of
Left err -> error$ "CryptoRandomGen splitGen error:"++ show err
Right (g1,g2) -> (CRGtoRG0 g1, CRGtoRG0 g2)
Right (g1,g2) -> (CRGtoRG_Unbuffered g1, CRGtoRG_Unbuffered g2)

-- Another option would be to amortize overhead by generating a large
-- buffer of random bits at once.
Expand Down
129 changes: 0 additions & 129 deletions Codec/Crypto/IntelAES.hs

This file was deleted.

8 changes: 4 additions & 4 deletions Codec/Crypto/IntelAES/AESNI.hs
Expand Up @@ -29,7 +29,7 @@ module Codec.Crypto.IntelAES.AESNI
, mkAESGen192, mkAESGen256

-- Inefficient version for testing:
, mkAESGen0, SimpleAESRNG0
, mkAESGen0, SimpleAESRNG_Unbuffered
, IntelAES, N128, N192, N256
-- Plus, instances exported of course.
)
Expand Down Expand Up @@ -87,9 +87,9 @@ mkAESGen256 seed = convertCRG gen


-- | TEMP: Inefficient version for testing.
type SimpleAESRNG0 = CRGtoRG0 (BCtoCRG (IntelAES N128))
mkAESGen0 :: Int -> SimpleAESRNG0
mkAESGen0 int = CRGtoRG0 gen
type SimpleAESRNG_Unbuffered = CRGtoRG_Unbuffered (BCtoCRG (IntelAES N128))
mkAESGen0 :: Int -> SimpleAESRNG_Unbuffered
mkAESGen0 int = CRGtoRG_Unbuffered gen
where
Right (gen :: BCtoCRG (IntelAES N128)) = newGen (B.append halfseed halfseed )
halfseed = encode word64
Expand Down
3 changes: 2 additions & 1 deletion Setup.hs
Expand Up @@ -39,6 +39,7 @@ my_clean desc () hooks flags = do
setCurrentDirectory "./cbits/"
system "make clean"
setCurrentDirectory ".."
system "rm -f benchmark-intel-aes-rng"
putStrLn$ " [intel-aes] Done. Now running normal cabal clean action.\n"
(cleanHook simpleUserHooks) desc () hooks flags

Expand Down Expand Up @@ -88,7 +89,7 @@ patchDesc desc localinfo = do
-- Whew... nested record updates are painful:
desc3 = desc { library = Just (lib { libBuildInfo = newlbi})}

putStrLn$ " [intel-aes] Modified package info. "
putStrLn$ " [intel-aes] Modified package description structure with extra options. "
return desc3


Expand Down
128 changes: 128 additions & 0 deletions System/Random/AES.hs
@@ -0,0 +1,128 @@
{-|
Module : System.Random.AES
Copyright : (c) Ryan Newton 2011
License : BSD-style (see the file LICENSE)
Maintainer : rrnewton@gmail.com
Stability : experimental
Portability : Mac OS, Linux, Untested on Windows
This module provides a random number generator based on AES both
using the System.Random.RandomGen interface and the
Codec.Crypto.Random one. The AES implementation that will test
the CPU ID and use hardware acceleration where available,
otherwise it will fall back to Dr. Brian Gladman's software
implementation.
-}
{-# OPTIONS_GHC -fwarn-unused-imports #-}
{-# LANGUAGE ForeignFunctionInterface, CPP, ScopedTypeVariables #-}

module System.Random.AES
(
mkAESGen, mkAESGenCRG,
AesCRG(), AesRG(),
supportsAESNI,
-- Plus, instances exported of course.
-- testIntelAES
)
where

import qualified Codec.Crypto.IntelAES.AESNI as NI
import qualified Codec.Crypto.GladmanAES as GA
-- import GHC.IO (unsafeDupablePerformIO)
import Data.Tagged
import Data.Word
import Data.Serialize
import qualified Data.ByteString as B
-- import Crypto.Random (CryptoRandomGen(..), GenError(..), splitGen, genBytes)
import Crypto.Random (CryptoRandomGen(..))
-- import Crypto.Types
import Codec.Crypto.ConvertRNG

-- This type represents an RNG which may have one of two different
-- representations, corresponding to the software or the hardware
-- supported version.
newtype AesCRG =
AesCRG
(Either (BCtoCRG (NI.IntelAES NI.N128))
(BCtoCRG (GA.AES GA.N128)))

-- | A type representing an AES-based random number generator which
-- will use AESNI instructions when available, and invoke the
-- portable Gladman implementation when not.
type AesRG = CRGtoRG AesCRG

-- | Simple function to create a random number generator from an Int,
-- exposing the `System.Random.RandomGen` interface, analogous to
-- `System.Random.newStdGen`. Only 128-bit encryption is currently
-- provided.
mkAESGen :: Int -> AesRG
mkAESGen int = convertCRG (mkAESGenCRG int)

-- | This variant creates an random number generator which exposes the
-- `Crypto.Random.CryptoRandomGen` interface.
mkAESGenCRG :: Int -> AesCRG
mkAESGenCRG int = gen
where
Right (gen :: AesCRG) = newGen (B.append halfseed halfseed )
halfseed = encode word64
word64 = fromIntegral int :: Word64



foreign import ccall unsafe "iaesni.h" check_for_aes_instructions :: Bool

-- | Does the machine support AESNI instructions?
supportsAESNI :: Bool
supportsAESNI = check_for_aes_instructions

-- | This instance provides the CryptoRandomGen interface, which
-- allows bulk generation of random bytes.
instance CryptoRandomGen AesCRG where

-- newGen :: B.ByteString -> Either GenError AesCRG
newGen =
if check_for_aes_instructions
-- Ick, boilerplate:
then \bytes -> case newGen bytes of Left err -> Left err
Right gen -> Right$ AesCRG$ Left gen
else \bytes -> case newGen bytes of Left err -> Left err
Right gen -> Right$ AesCRG$ Right gen

genSeedLength = Tagged 128

-- ByteLength -> AesCRG -> Either GenError (B.ByteString, AesCRG)
genBytes req (AesCRG (Left gen)) =

#if 0
-- UNFINISHED: Let's try to reduce that boilerplate if we can...
mapRight (mapSnd (AesCRG . Left) ) $ genBytes req gen
#else
case genBytes req gen of
Left err -> Left err
Right (bytes,gen') -> Right (bytes, AesCRG (Left gen'))
#endif


-- <boilerplate> OUCH
genBytes req (AesCRG (Right gen)) =
case genBytes req gen of
Left err -> Left err
Right (bytes,gen') -> Right (bytes, AesCRG (Right gen'))
reseed bs (AesCRG (Left gen)) =
case reseed bs gen of
Left err -> Left err
Right gen' -> Right (AesCRG (Left gen'))
reseed bs (AesCRG (Right gen)) =
case reseed bs gen of
Left err -> Left err
Right gen' -> Right (AesCRG (Right gen'))
-- </boilerplate>

-- UNFINISHED Refactoring:
{-# INLINE mapRight #-}
mapRight fn x@(Left _) = x
mapRight fn (Right x) = Right$ fn x
{-# INLINE mapSnd #-}
mapSnd fn (x,y) = (x,fn y)

0 comments on commit 3ad20dd

Please sign in to comment.