Merge pull request #281 from ocheron/cpu-options

Add module Crypto.System.CPU
This commit is contained in:
Olivier Chéron 2019-06-23 09:05:13 +02:00
commit cdd0821eee
5 changed files with 92 additions and 4 deletions

64
Crypto/System/CPU.hs Normal file
View File

@ -0,0 +1,64 @@
-- |
-- Module : Crypto.System.CPU
-- License : BSD-style
-- Maintainer : Olivier Chéron <olivier.cheron@gmail.com>
-- Stability : experimental
-- Portability : unknown
--
-- Gives information about cryptonite runtime environment.
--
{-# LANGUAGE CPP #-}
{-# LANGUAGE DeriveDataTypeable #-}
{-# LANGUAGE ForeignFunctionInterface #-}
module Crypto.System.CPU
( ProcessorOption (..)
, processorOptions
) where
import Data.Data
import Data.List (findIndices)
#ifdef SUPPORT_RDRAND
import Data.Maybe (isJust)
#endif
import Data.Word (Word8)
import Foreign.Ptr
import Foreign.Storable
import Crypto.Internal.Compat
#ifdef SUPPORT_RDRAND
import Crypto.Random.Entropy.RDRand
import Crypto.Random.Entropy.Source
#endif
-- | CPU options impacting cryptography implementation and libary performance.
data ProcessorOption
= AESNI -- ^ Support for AES instructions, with flag @support_aesni@
| PCLMUL -- ^ Support for CLMUL instructions, with flag @support_pclmuldq@
| RDRAND -- ^ Support for RDRAND instruction, with flag @support_rdrand@
deriving (Show,Eq,Enum,Data)
-- | Options which have been enabled at compile time and are supported by the
-- current CPU.
processorOptions :: [ProcessorOption]
processorOptions = unsafeDoIO $ do
p <- cryptonite_aes_cpu_init
options <- traverse (getOption p) aesOptions
rdrand <- hasRDRand
return (decodeOptions options ++ [ RDRAND | rdrand ])
where
aesOptions = [ AESNI .. PCLMUL ]
getOption p = peekElemOff p . fromEnum
decodeOptions = map toEnum . findIndices (> 0)
{-# NOINLINE processorOptions #-}
hasRDRand :: IO Bool
#ifdef SUPPORT_RDRAND
hasRDRand = fmap isJust getRDRand
where getRDRand = entropyOpen :: IO (Maybe RDRand)
#else
hasRDRand = return False
#endif
foreign import ccall unsafe "cryptonite_aes_cpu_init"
cryptonite_aes_cpu_init :: IO (Ptr Word8)

View File

@ -218,11 +218,19 @@ typedef void (*gf_mul_f)(block128 *a, const table_4bit htable);
#define cryptonite_gf_mul(a,t) cryptonite_aes_generic_gf_mul(a,t)
#endif
#define CPU_AESNI 0
#define CPU_PCLMUL 1
#define CPU_OPTION_COUNT 2
static uint8_t cryptonite_aes_cpu_options[CPU_OPTION_COUNT] = {};
#if defined(ARCH_X86) && defined(WITH_AESNI)
static void initialize_table_ni(int aesni, int pclmul)
{
if (!aesni)
return;
cryptonite_aes_cpu_options[CPU_AESNI] = 1;
cryptonite_aes_branch_table[INIT_128] = cryptonite_aesni_init;
cryptonite_aes_branch_table[INIT_256] = cryptonite_aesni_init;
@ -257,6 +265,8 @@ static void initialize_table_ni(int aesni, int pclmul)
#ifdef WITH_PCLMUL
if (!pclmul)
return;
cryptonite_aes_cpu_options[CPU_PCLMUL] = 1;
/* GHASH */
cryptonite_aes_branch_table[GHASH_HINIT] = cryptonite_aesni_hinit_pclmul,
cryptonite_aes_branch_table[GHASH_GF_MUL] = cryptonite_aesni_gf_mul_pclmul,
@ -265,6 +275,14 @@ static void initialize_table_ni(int aesni, int pclmul)
}
#endif
uint8_t *cryptonite_aes_cpu_init(void)
{
#if defined(ARCH_X86) && defined(WITH_AESNI)
cryptonite_aesni_initialize_hw(initialize_table_ni);
#endif
return cryptonite_aes_cpu_options;
}
void cryptonite_aes_initkey(aes_key *key, uint8_t *origkey, uint8_t size)
{
switch (size) {
@ -272,9 +290,7 @@ void cryptonite_aes_initkey(aes_key *key, uint8_t *origkey, uint8_t size)
case 24: key->nbr = 12; key->strength = 1; break;
case 32: key->nbr = 14; key->strength = 2; break;
}
#if defined(ARCH_X86) && defined(WITH_AESNI)
cryptonite_aesni_initialize_hw(initialize_table_ni);
#endif
cryptonite_aes_cpu_init();
init_f _init = GET_INIT(key->strength);
_init(key, origkey, size);
}

View File

@ -115,4 +115,6 @@ void cryptonite_aes_ccm_encrypt(uint8_t *output, aes_ccm *ccm, aes_key *key, uin
void cryptonite_aes_ccm_decrypt(uint8_t *output, aes_ccm *ccm, aes_key *key, uint8_t *input, uint32_t length);
void cryptonite_aes_ccm_finish(uint8_t *tag, aes_ccm *ccm, aes_key *key);
uint8_t *cryptonite_aes_cpu_init(void);
#endif

View File

@ -177,6 +177,7 @@ Library
Crypto.Random.Entropy
Crypto.Random.EntropyPool
Crypto.Random.Entropy.Unsafe
Crypto.System.CPU
Crypto.Tutorial
Other-modules: Crypto.Cipher.AES.Primitive
Crypto.Cipher.Blowfish.Box

View File

@ -3,6 +3,8 @@ module Main where
import Imports
import Crypto.System.CPU
import qualified Number
import qualified Number.F2m
import qualified BCrypt
@ -43,7 +45,10 @@ import qualified KAT_AFIS
import qualified Padding
tests = testGroup "cryptonite"
[ Number.tests
[ testGroup "runtime"
[ testCaseInfo "CPU" (return $ show processorOptions)
]
, Number.tests
, Number.F2m.tests
, Hash.tests
, Padding.tests