From ee3e5e69bf004007b9e3dd3f6705f13b08b21303 Mon Sep 17 00:00:00 2001 From: Vincent Hanquez Date: Mon, 11 May 2015 07:11:38 +0100 Subject: [PATCH] [number] move some number primitive to use compat without CPP --- Crypto/Number/Basic.hs | 42 +++++++---------------------------------- Crypto/Number/Prime.hs | 43 ++++++++++++++---------------------------- 2 files changed, 21 insertions(+), 64 deletions(-) diff --git a/Crypto/Number/Basic.hs b/Crypto/Number/Basic.hs index 0d79e55..02c0f21 100644 --- a/Crypto/Number/Basic.hs +++ b/Crypto/Number/Basic.hs @@ -1,14 +1,3 @@ -{-# LANGUAGE BangPatterns #-} -{-# LANGUAGE CPP #-} -#ifndef MIN_VERSION_integer_gmp -#define MIN_VERSION_integer_gmp(a,b,c) 0 -#endif -#if MIN_VERSION_integer_gmp(0,5,1) -{-# LANGUAGE UnboxedTuples #-} -#endif -#ifdef VERSION_integer_gmp -{-# LANGUAGE MagicHash #-} -#endif -- | -- Module : Crypto.Number.Basic -- License : BSD-style @@ -16,6 +5,7 @@ -- Stability : experimental -- Portability : Good +{-# LANGUAGE BangPatterns #-} module Crypto.Number.Basic ( sqrti , gcde @@ -23,15 +13,7 @@ module Crypto.Number.Basic , log2 ) where -#if MIN_VERSION_integer_gmp(0,5,1) -import GHC.Integer.GMP.Internals -#else -import Data.Bits -#endif -#ifdef VERSION_integer_gmp -import GHC.Exts -import GHC.Integer.Logarithms (integerLog2#) -#endif +import Crypto.Number.Compat -- | sqrti returns two integer (l,b) so that l <= sqrt i <= b -- the implementation is quite naive, use an approximation for the first number @@ -70,35 +52,25 @@ sqrti i -- gcde 'a' 'b' find (x,y,gcd(a,b)) where ax + by = d -- gcde :: Integer -> Integer -> (Integer, Integer, Integer) -#if MIN_VERSION_integer_gmp(0,5,1) -gcde a b = (s, t, g) - where (# g, s #) = gcdExtInteger a b - t = (g - s * a) `div` b -#else -gcde a b = if d < 0 then (-x,-y,-d) else (x,y,d) where +gcde a b = onGmpUnsupported (gmpGcde a b) $ + if d < 0 then (-x,-y,-d) else (x,y,d) + where (d, x, y) = f (a,1,0) (b,0,1) f t (0, _, _) = t f (a', sa, ta) t@(b', sb, tb) = let (q, r) = a' `divMod` b' in f t (r, sa - (q * sb), ta - (q * tb)) -#endif - -- | check if a list of integer are all even areEven :: [Integer] -> Bool areEven = and . map even log2 :: Integer -> Int -#ifdef VERSION_integer_gmp -log2 0 = 0 -log2 x = I# (integerLog2# x) -#else --- http://www.haskell.org/pipermail/haskell-cafe/2008-February/039465.html -log2 = imLog 2 +log2 n = onGmpUnsupported (gmpLog2 n) $ imLog 2 n where + -- http://www.haskell.org/pipermail/haskell-cafe/2008-February/039465.html imLog b x = if x < b then 0 else (x `div` b^l) `doDiv` l where l = 2 * imLog (b * b) x doDiv x' l' = if x' < b then l' else (x' `div` b) `doDiv` (l' + 1) -#endif {-# INLINE log2 #-} diff --git a/Crypto/Number/Prime.hs b/Crypto/Number/Prime.hs index 8bec6b2..93aa1d5 100644 --- a/Crypto/Number/Prime.hs +++ b/Crypto/Number/Prime.hs @@ -5,14 +5,7 @@ -- Stability : experimental -- Portability : Good -{-# LANGUAGE CPP #-} {-# LANGUAGE BangPatterns #-} -#ifndef MIN_VERSION_integer_gmp -#define MIN_VERSION_integer_gmp(a,b,c) 0 -#endif -#if MIN_VERSION_integer_gmp(0,5,1) -{-# LANGUAGE MagicHash #-} -#endif module Crypto.Number.Prime ( generatePrime @@ -28,17 +21,13 @@ module Crypto.Number.Prime import Crypto.Internal.Imports +import Crypto.Number.Compat import Crypto.Number.Generate import Crypto.Number.Basic (sqrti, gcde) import Crypto.Number.ModArithmetic (exponantiation) import Crypto.Random.Types -#if MIN_VERSION_integer_gmp(0,5,1) -import GHC.Integer.GMP.Internals -import GHC.Base -#else import Data.Bits -#endif -- | returns if the number is probably prime. -- first a list of small primes are implicitely tested for divisibility, @@ -84,27 +73,24 @@ findPrimeFromWith prop !n -- | find a prime from a starting point with no specific property. findPrimeFrom :: MonadRandom m => Integer -> m Integer findPrimeFrom n = -#if MIN_VERSION_integer_gmp(0,5,1) - return $ nextPrimeInteger n -#else - findPrimeFromWith (\_ -> return True) n -#endif + case gmpNextPrime n of + GmpSupported p -> return p + GmpUnsupported -> findPrimeFromWith (\_ -> return True) n -- | Miller Rabin algorithm return if the number is probably prime or composite. -- the tries parameter is the number of recursion, that determines the accuracy of the test. primalityTestMillerRabin :: MonadRandom m => Int -> Integer -> m Bool -#if MIN_VERSION_integer_gmp(0,5,1) -primalityTestMillerRabin (I# tries) !n = - case testPrimeInteger n tries of - 0# -> return False - _ -> return True -#else -primalityTestMillerRabin tries !n - | n <= 3 = error "Miller-Rabin requires tested value to be > 3" - | even n = return False - | tries <= 0 = error "Miller-Rabin tries need to be > 0" - | otherwise = loop <$> generateTries tries +primalityTestMillerRabin tries !n = + case gmpTestPrimeMillerRabin tries n of + GmpSupported b -> return b + GmpUnsupported -> run where + run + | n <= 3 = error "Miller-Rabin requires tested value to be > 3" + | even n = return False + | tries <= 0 = error "Miller-Rabin tries need to be > 0" + | otherwise = loop <$> generateTries tries + !nm1 = n-1 !nm2 = n-2 @@ -136,7 +122,6 @@ primalityTestMillerRabin tries !n | x2 == 1 = False | x2 /= nm1 = loop' ws ((x2*x2) `mod` n) (r+1) | otherwise = loop ws -#endif {- n < z -> witness to test