module Crypto.Number.Generate
( GenTopPolicy(..)
, generateParams
, generateMax
, generateBetween
) where
import Crypto.Internal.Imports
import Crypto.Number.Basic
import Crypto.Number.Serialize
import Crypto.Random.Types
import Control.Monad (when)
import Foreign.Ptr
import Foreign.Storable
import Data.Bits ((.|.), (.&.), shiftL, complement, testBit)
import Crypto.Internal.ByteArray (ScrubbedBytes)
import qualified Crypto.Internal.ByteArray as B
data GenTopPolicy =
SetHighest
| SetTwoHighest
deriving (Int -> GenTopPolicy -> ShowS
[GenTopPolicy] -> ShowS
GenTopPolicy -> String
forall a.
(Int -> a -> ShowS) -> (a -> String) -> ([a] -> ShowS) -> Show a
showList :: [GenTopPolicy] -> ShowS
$cshowList :: [GenTopPolicy] -> ShowS
show :: GenTopPolicy -> String
$cshow :: GenTopPolicy -> String
showsPrec :: Int -> GenTopPolicy -> ShowS
$cshowsPrec :: Int -> GenTopPolicy -> ShowS
Show,GenTopPolicy -> GenTopPolicy -> Bool
forall a. (a -> a -> Bool) -> (a -> a -> Bool) -> Eq a
/= :: GenTopPolicy -> GenTopPolicy -> Bool
$c/= :: GenTopPolicy -> GenTopPolicy -> Bool
== :: GenTopPolicy -> GenTopPolicy -> Bool
$c== :: GenTopPolicy -> GenTopPolicy -> Bool
Eq)
generateParams :: MonadRandom m
=> Int
-> Maybe GenTopPolicy
-> Bool
-> m Integer
generateParams :: forall (m :: * -> *).
MonadRandom m =>
Int -> Maybe GenTopPolicy -> Bool -> m Integer
generateParams Int
bits Maybe GenTopPolicy
genTopPolicy Bool
generateOdd
| Int
bits forall a. Ord a => a -> a -> Bool
<= Int
0 = forall (m :: * -> *) a. Monad m => a -> m a
return Integer
0
| Bool
otherwise = forall ba. ByteArrayAccess ba => ba -> Integer
os2ip forall b c a. (b -> c) -> (a -> b) -> a -> c
. ScrubbedBytes -> ScrubbedBytes
tweak forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *) byteArray.
(MonadRandom m, ByteArray byteArray) =>
Int -> m byteArray
getRandomBytes Int
bytes
where
tweak :: ScrubbedBytes -> ScrubbedBytes
tweak :: ScrubbedBytes -> ScrubbedBytes
tweak ScrubbedBytes
orig = forall bs1 bs2 p.
(ByteArrayAccess bs1, ByteArray bs2) =>
bs1 -> (Ptr p -> IO ()) -> bs2
B.copyAndFreeze ScrubbedBytes
orig forall a b. (a -> b) -> a -> b
$ \Ptr Word8
p0 -> do
let p1 :: Ptr b
p1 = Ptr Word8
p0 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` Int
1
pEnd :: Ptr b
pEnd = Ptr Word8
p0 forall a b. Ptr a -> Int -> Ptr b
`plusPtr` (Int
bytes forall a. Num a => a -> a -> a
- Int
1)
case Maybe GenTopPolicy
genTopPolicy of
Maybe GenTopPolicy
Nothing -> forall (m :: * -> *) a. Monad m => a -> m a
return ()
Just GenTopPolicy
SetHighest -> Ptr Word8
p0 Ptr Word8 -> Word8 -> IO ()
|= (Word8
1 forall a. Bits a => a -> Int -> a
`shiftL` Int
bit)
Just GenTopPolicy
SetTwoHighest
| Int
bit forall a. Eq a => a -> a -> Bool
== Int
0 -> do Ptr Word8
p0 Ptr Word8 -> Word8 -> IO ()
$= Word8
0x1
forall {b}. Ptr b
p1 Ptr Word8 -> Word8 -> IO ()
|= Word8
0x80
| Bool
otherwise -> Ptr Word8
p0 Ptr Word8 -> Word8 -> IO ()
|= (Word8
0x3 forall a. Bits a => a -> Int -> a
`shiftL` (Int
bit forall a. Num a => a -> a -> a
- Int
1))
Ptr Word8
p0 Ptr Word8 -> Word8 -> IO ()
&= (forall a. Bits a => a -> a
complement forall a b. (a -> b) -> a -> b
$ Word8
mask)
forall (f :: * -> *). Applicative f => Bool -> f () -> f ()
when Bool
generateOdd (forall {b}. Ptr b
pEnd Ptr Word8 -> Word8 -> IO ()
|= Word8
0x1)
($=) :: Ptr Word8 -> Word8 -> IO ()
$= :: Ptr Word8 -> Word8 -> IO ()
($=) Ptr Word8
p Word8
w = forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p Word8
w
(|=) :: Ptr Word8 -> Word8 -> IO ()
|= :: Ptr Word8 -> Word8 -> IO ()
(|=) Ptr Word8
p Word8
w = forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Word8
v -> forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p (Word8
v forall a. Bits a => a -> a -> a
.|. Word8
w)
(&=) :: Ptr Word8 -> Word8 -> IO ()
&= :: Ptr Word8 -> Word8 -> IO ()
(&=) Ptr Word8
p Word8
w = forall a. Storable a => Ptr a -> IO a
peek Ptr Word8
p forall (m :: * -> *) a b. Monad m => m a -> (a -> m b) -> m b
>>= \Word8
v -> forall a. Storable a => Ptr a -> a -> IO ()
poke Ptr Word8
p (Word8
v forall a. Bits a => a -> a -> a
.&. Word8
w)
bytes :: Int
bytes = (Int
bits forall a. Num a => a -> a -> a
+ Int
7) forall a. Integral a => a -> a -> a
`div` Int
8;
bit :: Int
bit = (Int
bits forall a. Num a => a -> a -> a
- Int
1) forall a. Integral a => a -> a -> a
`mod` Int
8;
mask :: Word8
mask = Word8
0xff forall a. Bits a => a -> Int -> a
`shiftL` (Int
bit forall a. Num a => a -> a -> a
+ Int
1);
generateMax :: MonadRandom m
=> Integer
-> m Integer
generateMax :: forall (m :: * -> *). MonadRandom m => Integer -> m Integer
generateMax Integer
range
| Integer
range forall a. Ord a => a -> a -> Bool
<= Integer
1 = forall (m :: * -> *) a. Monad m => a -> m a
return Integer
0
| Integer
range forall a. Ord a => a -> a -> Bool
< Integer
127 = m Integer
generateSimple
| Bool
canOverGenerate = forall {t} {m :: * -> *}.
(Eq t, Num t, MonadRandom m) =>
t -> m Integer
loopGenerateOver Int
tries
| Bool
otherwise = forall {t} {m :: * -> *}.
(Eq t, Num t, MonadRandom m) =>
t -> m Integer
loopGenerate Int
tries
where
generateSimple :: m Integer
generateSimple = forall a b c. (a -> b -> c) -> b -> a -> c
flip forall a. Integral a => a -> a -> a
mod Integer
range forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
`fmap` forall (m :: * -> *).
MonadRandom m =>
Int -> Maybe GenTopPolicy -> Bool -> m Integer
generateParams Int
bits forall a. Maybe a
Nothing Bool
False
loopGenerate :: t -> m Integer
loopGenerate t
count
| t
count forall a. Eq a => a -> a -> Bool
== t
0 = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"internal: generateMax(" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
range forall a. [a] -> [a] -> [a]
++ String
" bits=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
bits forall a. [a] -> [a] -> [a]
++ String
") (normal) doesn't seems to work properly"
| Bool
otherwise = do
Integer
r <- forall (m :: * -> *).
MonadRandom m =>
Int -> Maybe GenTopPolicy -> Bool -> m Integer
generateParams Int
bits forall a. Maybe a
Nothing Bool
False
if Integer -> Bool
isValid Integer
r then forall (m :: * -> *) a. Monad m => a -> m a
return Integer
r else t -> m Integer
loopGenerate (t
countforall a. Num a => a -> a -> a
-t
1)
loopGenerateOver :: t -> m Integer
loopGenerateOver t
count
| t
count forall a. Eq a => a -> a -> Bool
== t
0 = forall a. HasCallStack => String -> a
error forall a b. (a -> b) -> a -> b
$ String
"internal: generateMax(" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Integer
range forall a. [a] -> [a] -> [a]
++ String
" bits=" forall a. [a] -> [a] -> [a]
++ forall a. Show a => a -> String
show Int
bits forall a. [a] -> [a] -> [a]
++ String
") (over) doesn't seems to work properly"
| Bool
otherwise = do
Integer
r <- forall (m :: * -> *).
MonadRandom m =>
Int -> Maybe GenTopPolicy -> Bool -> m Integer
generateParams (Int
bitsforall a. Num a => a -> a -> a
+Int
1) forall a. Maybe a
Nothing Bool
False
let r2 :: Integer
r2 = Integer
r forall a. Num a => a -> a -> a
- Integer
range
r3 :: Integer
r3 = Integer
r2 forall a. Num a => a -> a -> a
- Integer
range
if Integer -> Bool
isValid Integer
r
then forall (m :: * -> *) a. Monad m => a -> m a
return Integer
r
else if Integer -> Bool
isValid Integer
r2
then forall (m :: * -> *) a. Monad m => a -> m a
return Integer
r2
else if Integer -> Bool
isValid Integer
r3
then forall (m :: * -> *) a. Monad m => a -> m a
return Integer
r3
else t -> m Integer
loopGenerateOver (t
countforall a. Num a => a -> a -> a
-t
1)
bits :: Int
bits = Integer -> Int
numBits Integer
range
canOverGenerate :: Bool
canOverGenerate = Int
bits forall a. Ord a => a -> a -> Bool
> Int
3 Bool -> Bool -> Bool
&& Bool -> Bool
not (Integer
range forall a. Bits a => a -> Int -> Bool
`testBit` (Int
bitsforall a. Num a => a -> a -> a
-Int
2)) Bool -> Bool -> Bool
&& Bool -> Bool
not (Integer
range forall a. Bits a => a -> Int -> Bool
`testBit` (Int
bitsforall a. Num a => a -> a -> a
-Int
3))
isValid :: Integer -> Bool
isValid Integer
n = Integer
n forall a. Ord a => a -> a -> Bool
< Integer
range
tries :: Int
tries :: Int
tries = Int
100
generateBetween :: MonadRandom m => Integer -> Integer -> m Integer
generateBetween :: forall (m :: * -> *).
MonadRandom m =>
Integer -> Integer -> m Integer
generateBetween Integer
low Integer
high = (Integer
low forall a. Num a => a -> a -> a
+) forall (f :: * -> *) a b. Functor f => (a -> b) -> f a -> f b
<$> forall (m :: * -> *). MonadRandom m => Integer -> m Integer
generateMax (Integer
high forall a. Num a => a -> a -> a
- Integer
low forall a. Num a => a -> a -> a
+ Integer
1)